|
Database.HaskellDB | Portability | non portable | Stability | experimental | Maintainer | haskelldb-users@lists.sourceforge.net |
|
|
|
|
|
Description |
HaskellDB is a Haskell library for expressing database queries and
operations in a type safe and declarative way. HaskellDB compiles a
relational algebra-like syntax into SQL, submits the operations to the
database for processing, and returns the results as ordinary Haskell
values.
This is the main module that the user should
import. Beside this module, the user should import a
particular database binding (ie. Database.HaskellDB.HSQL.ODBC)
and database definitions.
HaskellDB was originally written by Daan Leijen and it's
design is described in the paper Domain Specific Embedded
Compilers, Daan Leijen and Erik Meijer. 2nd USENIX
Conference on Domain-Specific Languages (DSL), Austin,
USA, October 1999 (http://www.usenix.org/events/dsl99/).
This new version of HaskellDB was produced as a student project at
Chalmers University of Technology in Gothenburg, Sweden. The aim of the
project was to make HaskellDB a practically useful database library.
That work is described in
Student Paper: HaskellDB Improved,
Björn Bringert, Anders Höckersten, Conny Andersson, Martin Andersson,
Mary Bergman, Victor Blomqvist and Torbjörn Martin.
In Proceedings of the ACM SIGPLAN 2004 Haskell Workshop, Snowbird, Utah,
USA, September 22, 2004.
(http://haskelldb.sourceforge.net/haskelldb.pdf)
|
|
Synopsis |
|
|
|
Documentation |
|
data Rel r |
Type of relations, contains the attributes
of the relation and an Alias to which the
attributes are renamed in the PrimQuery.
| Instances | |
|
|
data Attr f a |
Typed attributes
| Instances | |
|
|
data Expr a |
Type of normal expressions, contains the untyped PrimExpr.
| Instances | |
|
|
data Table r |
Basic tables, contains table name and an
association from attributes to attribute
names in the real table.
|
|
|
data Query a |
Instances | |
|
|
data OrderExpr |
Instances | |
|
|
Records
|
|
class HasField f r |
The record r has the field f if there is an instance of
HasField f r.
| | Instances | |
|
|
type Record r = RecNil -> r |
The type used for records. This is a function
that takes a RecNil so that the user does not have to
put a RecNil at the end of every record.
|
|
class Select f r a | f r -> a where |
| Methods | (!) :: r -> f -> a | Field selection operator. It is overloaded so that
users (read HaskellDB) can redefine it for things
with phantom record types.
|
| | Instances | |
|
|
(#) |
:: Record (RecCons f a RecNil) | Field to add
| -> (b -> c) | Rest of record
| -> (b -> RecCons f a c) | New record
| Adds the field from a one-field record to another record.
|
|
|
(<<) |
:: Attr f a | Label
| -> e a | Expression
| -> Record (RecCons f (e a) RecNil) | New record
| Creates a record field.
Similar to '(.=.)', but gets the field label from an Attr.
|
|
|
(<<-) |
:: ShowConstant a | | => Attr f a | Field label
| -> a | Field value
| -> Record (RecCons f (Expr a) RecNil) | New record
| Convenience operator for constructing records of constants.
Useful primarily with insert.
f <<- x is the same as f << constant x
|
|
|
(!) :: Select f r a => r -> f -> a |
Field selection operator. It is overloaded so that
users (read HaskellDB) can redefine it for things
with phantom record types.
|
|
(!.) :: Select f r a => r -> f -> a |
The (!.) operator selects over returned records from
the database (= rows)
Non-overloaded version of '!'. For backwards compatibility.
|
|
Relational operators
|
|
restrict :: Expr Bool -> Query () |
Restricts the records to only those who evaluates the
expression to True.
|
|
table :: ShowRecRow r => Table r -> Query (Rel r) |
Return all records from a specific table.
|
|
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er) |
Specifies a subset of the columns in the table.
|
|
union :: Query (Rel r) -> Query (Rel r) -> Query (Rel r) |
Return all records which are present in at least
one of the relations.
|
|
intersect :: Query (Rel r) -> Query (Rel r) -> Query (Rel r) |
Return all records which are present in both relations.
|
|
divide :: Query (Rel r) -> Query (Rel r) -> Query (Rel r) |
Not in SQL92.
|
|
minus :: Query (Rel r) -> Query (Rel r) -> Query (Rel r) |
Return all records from the first relation that are not
present in the second relation.
|
|
Query expressions
|
|
(.==.) :: Eq a => Expr a -> Expr a -> Expr Bool |
(.==.) is used in a similar way as the standard op (==) in
Haskell and = in SQL, but takes two Expr as arguments and
returns an Expr Bool.
|
|
(.<>.) :: Eq a => Expr a -> Expr a -> Expr Bool |
(.<>.) is used in a similar way as the standard op (/=) in
Haskell and <> in SQL, but takes two Expr as arguments and
returns an Expr Bool.
|
|
(.<.) :: Ord a => Expr a -> Expr a -> Expr Bool |
As with (.==.) and (.<>.), this op has a standard Haskell
op counterpart; (<) and an SQL counterpart; <
|
|
(.<=.) :: Ord a => Expr a -> Expr a -> Expr Bool |
As with (.==.) and (.<>.), this op have a standard Haskell
op counterpart, (<=) and an SQL counterpart; <=.
|
|
(.>.) :: Ord a => Expr a -> Expr a -> Expr Bool |
As with (.==.) and (.<>.), this op have a standard Haskell
op counterpart, (>) and an SQL counterpart; >.
|
|
(.>=.) :: Ord a => Expr a -> Expr a -> Expr Bool |
As with (.==.) and (.<>.), this op have a standard Haskell
op counterpart, (>=) and an SQL counterpart; >=.
|
|
(.&&.) :: Expr Bool -> Expr Bool -> Expr Bool |
"Logical and" on Expr, similar to the (&&) op in
Haskell and AND in SQL.
|
|
(.||.) :: Expr Bool -> Expr Bool -> Expr Bool |
"Logical or" on Expr, similar to the (||) op in
Haskell and OR in SQL.
|
|
(.*.) :: Num a => Expr a -> Expr a -> Expr a |
Multiplication
|
|
(./.) :: Num a => Expr a -> Expr a -> Expr a |
Division
|
|
(.%.) :: Num a => Expr a -> Expr a -> Expr a |
Modulo
|
|
(.+.) :: Num a => Expr a -> Expr a -> Expr a |
Addition
|
|
(.-.) :: Num a => Expr a -> Expr a -> Expr a |
Subtraction
|
|
(.++.) :: Expr String -> Expr String -> Expr String |
Concatenates two String-expressions.
|
|
_not :: Expr Bool -> Expr Bool |
The inverse of an Expr Bool.
|
|
like :: Expr String -> Expr String -> Expr Bool |
The HaskellDB counterpart to the SQL LIKE keyword.
In the expresions, % is a wildcard representing any characters
in the same position relavtive to the given characters and
_ is a wildcard representing one character e.g.
like (constant "ABCDEFFF") (constant "AB%F_F")
is true while
like (constant "ABCDEF") (constant "AC%F")
is false.
Note that SQL92 does not specify whether LIKE is case-sensitive or not.
Different database systems implement this differently.
|
|
_in :: Eq a => Expr a -> [Expr a] -> Expr Bool |
Returns true if the value of the first operand is
equal to the value of any of the expressions in the
list operand.
|
|
cat :: Expr String -> Expr String -> Expr String |
Produces the concatenation of two String-expressions.
|
|
_length :: Expr String -> Expr Int |
Gets the length of a string.
|
|
isNull :: Expr a -> Expr Bool |
Returns true if the expression is Null.
|
|
notNull :: Expr a -> Expr Bool |
The inverse of isNull, returns false
if the expression supplied is Null.
|
|
fromNull |
:: Expr a | Default value (to be returned for Nothing)
| -> Expr (Maybe a) | A nullable expression
| -> Expr a | | Takes a default value a and a nullable value. If the value is NULL,
the default value is returned, otherwise the value itself is returned.
Simliar to fromMaybe
|
|
|
constant :: ShowConstant a => a -> Expr a |
Creates a constant expression from a haskell value.
|
|
constJust :: ShowConstant a => a -> Expr (Maybe a) |
Turn constant data into a nullable expression.
Same as constant . Just
|
|
count :: Expr a -> ExprAggr Int |
Returns the number of records (=rows) in a query.
|
|
_sum :: Num a => Expr a -> ExprAggr a |
Returns the total sum of a column.
|
|
_max :: Ord a => Expr a -> ExprAggr a |
Returns the highest value of a column.
|
|
_min :: Ord a => Expr a -> ExprAggr a |
Returns the lowest value of a column.
|
|
avg :: Num a => Expr a -> ExprAggr a |
Returns the average of a column.
|
|
stddev :: Num a => Expr a -> ExprAggr a |
Returns the standard deviation of a column.
|
|
stddevP :: Num a => Expr a -> ExprAggr a |
|
variance :: Num a => Expr a -> ExprAggr a |
Returns the standard variance of a column.
|
|
varianceP :: Num a => Expr a -> ExprAggr a |
|
asc :: HasField f r => Rel r -> Attr f a -> OrderExpr |
Use this together with the function order to
order the results of a query in ascending order.
Takes a relation and an attribute of that relation, which
is used for the ordering.
|
|
desc :: HasField f r => Rel r -> Attr f a -> OrderExpr |
Use this together with the function order to
order the results of a query in descending order.
Takes a relation and an attribute of that relation, which
is used for the ordering.
|
|
order :: [OrderExpr] -> Query () |
Order the results of a query.
Use this with the asc or desc functions.
|
|
top :: Int -> Query () |
Return the n topmost records.
|
|
_case |
:: [(Expr Bool, Expr a)] | A list of conditions and expressions.
| -> Expr a | Else-expression.
| -> Expr a | | Creates a conditional expression.
Returns the value of the expression corresponding to the first
true condition. If none of the conditions are true, the value of
the else-expression is returned.
|
|
|
_default :: ExprDefault a |
The default value of the column. Only works with insert.
|
|
Database operations
|
|
data Database |
|
|
query :: GetRec er vr => Database -> Query (Rel er) -> IO [Record vr] |
performs a query on a database
|
|
insert :: (ToPrimExprs r, ShowRecRow r, InsertRec r er) => Database -> Table er -> Record r -> IO () |
Inserts a record into a table
|
|
delete |
:: ShowRecRow r | | => Database | The database
| -> Table r | The table to delete records from
| -> (Rel r -> Expr Bool) | Predicate used to select records to delete
| -> IO () | | deletes a bunch of records
|
|
|
update |
|
|
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO () |
Inserts values from a query into a table
|
|
tables |
:: Database | Database
| -> IO [TableName] | Names of all tables in the database
| List all tables in the database
|
|
|
describe |
:: Database | Database
| -> TableName | Name of the tables whose columns are to be listed
| -> IO [(Attribute, FieldDesc)] | Name and type info for each column
| List all columns in a table, along with their types
|
|
|
transaction |
:: Database | Database
| -> IO a | Action to run
| -> IO a | | Performs some database action in a transaction. If no exception is thrown,
the changes are committed.
|
|
|
Debugging
|
|
showQuery :: Query (Rel r) -> String |
Shows the optimized PrimQuery.
|
|
showQueryUnOpt :: Query (Rel r) -> String |
Shows the unoptimized PrimQuery.
|
|
showSql :: Query (Rel r) -> String |
Shows the optimized SQL query.
|
|
showSqlUnOpt :: Query (Rel r) -> String |
Shows the unoptimized SQL query.
|
|
Produced by Haddock version 0.8 |