haskelldb-0.12: SQL unwrapper for Haskell.Source codeContentsIndex
Database.HaskellDB
Portabilitynon portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Contents
Records
Relational operators
Query expressions
Database operations
Debugging
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, Bjrn Bringert, Anders Hckersten, Conny Andersson, Martin Andersson, Mary Bergman, Victor Blomqvist and Torbjrn Martin. In Proceedings of the ACM SIGPLAN 2004 Haskell Workshop, Snowbird, Utah, USA, September 22, 2004. (http://haskelldb.sourceforge.net/haskelldb.pdf)

Synopsis
data Rel r
data Attr f a
data Expr a
data Table r
data Query a
data OrderExpr
class HasField f r
type Record r = RecNil -> r
class Select f r a | f r -> a where
(!) :: r -> f -> a
(#) :: Record (RecCons f a RecNil) -> (b -> c) -> b -> RecCons f a c
(<<) :: Attr f a -> e a -> Record (RecCons f (e a) RecNil)
(<<-) :: ShowConstant a => Attr f a -> a -> Record (RecCons f (Expr a) RecNil)
(!.) :: Select f r a => r -> f -> a
restrict :: Expr Bool -> Query ()
table :: ShowRecRow r => Table r -> Query (Rel r)
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er)
unique :: Query ()
union :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)
intersect :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)
divide :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)
minus :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)
(.==.) :: Eq a => Expr a -> Expr a -> Expr Bool
(.<>.) :: Eq a => Expr a -> Expr a -> Expr Bool
(.<.) :: Ord a => Expr a -> Expr a -> Expr Bool
(.<=.) :: Ord a => Expr a -> Expr a -> Expr Bool
(.>.) :: Ord a => Expr a -> Expr a -> Expr Bool
(.>=.) :: Ord a => Expr a -> Expr a -> Expr Bool
(.&&.) :: Expr Bool -> Expr Bool -> Expr Bool
(.||.) :: Expr Bool -> Expr Bool -> Expr Bool
(.*.) :: Num a => Expr a -> Expr a -> Expr a
(./.) :: Num a => Expr a -> Expr a -> Expr a
(.%.) :: Num a => Expr a -> Expr a -> Expr a
(.+.) :: Num a => Expr a -> Expr a -> Expr a
(.-.) :: Num a => Expr a -> Expr a -> Expr a
(.++.) :: Expr String -> Expr String -> Expr String
_not :: Expr Bool -> Expr Bool
like :: Expr String -> Expr String -> Expr Bool
_in :: Eq a => Expr a -> [Expr a] -> Expr Bool
cat :: Expr String -> Expr String -> Expr String
_length :: Expr String -> Expr Int
isNull :: Expr a -> Expr Bool
notNull :: Expr a -> Expr Bool
fromNull :: Expr a -> Expr (Maybe a) -> Expr a
constant :: ShowConstant a => a -> Expr a
constJust :: ShowConstant a => a -> Expr (Maybe a)
count :: Expr a -> ExprAggr Int
_sum :: Num a => Expr a -> ExprAggr a
_max :: Ord a => Expr a -> ExprAggr a
_min :: Ord a => Expr a -> ExprAggr a
avg :: Num a => Expr a -> ExprAggr a
stddev :: Num a => Expr a -> ExprAggr a
stddevP :: Num a => Expr a -> ExprAggr a
variance :: Num a => Expr a -> ExprAggr a
varianceP :: Num a => Expr a -> ExprAggr a
asc :: HasField f r => Rel r -> Attr f a -> OrderExpr
desc :: HasField f r => Rel r -> Attr f a -> OrderExpr
order :: [OrderExpr] -> Query ()
top :: Int -> Query ()
_case :: [(Expr Bool, Expr a)] -> Expr a -> Expr a
_default :: ExprDefault a
data Database
query :: GetRec er vr => Database -> Query (Rel er) -> IO [Record vr]
insert :: (ToPrimExprs r, ShowRecRow r, InsertRec r er) => Database -> Table er -> Record r -> IO ()
delete :: ShowRecRow r => Database -> Table r -> (Rel r -> Expr Bool) -> IO ()
update :: (ShowLabels s, ToPrimExprs s) => Database -> Table r -> (Rel r -> Expr Bool) -> (Rel r -> Record s) -> IO ()
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO ()
tables :: Database -> IO [TableName]
describe :: Database -> TableName -> IO [(Attribute, FieldDesc)]
transaction :: Database -> IO a -> IO a
showQuery :: Query (Rel r) -> String
showQueryUnOpt :: Query (Rel r) -> String
showSql :: Query (Rel r) -> String
showSqlUnOpt :: Query (Rel r) -> String
Documentation
data Rel r Source
Type of relations, contains the attributes of the relation and an Alias to which the attributes are renamed in the PrimQuery.
show/hide Instances
Show (Query (Rel r))
ExprTypes r => ExprTypes (Rel r)
ExprType a => ExprType (Rel a)
HasField f r => Select (Attr f a) (Rel r) (Expr a)
data Attr f a Source
Typed attributes
show/hide Instances
HasField f r => Select (Attr f a) (Rel r) (Expr a)
data Expr a Source
Type of normal expressions, contains the untyped PrimExpr.
show/hide Instances
ProjectExpr Expr
InsertExpr Expr
ExprC Expr
Read (Expr a)
Show (Expr a)
ExprType a => ExprType (Expr a)
HasField f r => Select (Attr f a) (Rel r) (Expr a)
(ShowConstant a, ConstantRecord r cr) => ConstantRecord (RecCons f a r) (RecCons f (Expr a) cr)
(ProjectExpr e, ProjectRec r er) => ProjectRec (RecCons f (e a) r) (RecCons f (Expr a) er)
(InsertExpr e, InsertRec r er) => InsertRec (RecCons f (e a) r) (RecCons f (Expr a) er)
(GetValue a, GetRec er vr) => GetRec (RecCons f (Expr a) er) (RecCons f a vr)
data Table r Source
Basic tables, contains table name and an association from attributes to attribute names in the real table.
data Query a Source
show/hide Instances
data OrderExpr Source
show/hide Instances
Records
class HasField f r Source
The record r has the field f if there is an instance of HasField f r.
show/hide Instances
HasField f r => HasField f (Record r)
HasField f r => HasField f (RecCons g a r)
HasField f (RecCons f a r)
type Record r = RecNil -> rSource
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 whereSource
Methods
(!) :: r -> f -> aSource
Field selection operator. It is overloaded so that users (read HaskellDB) can redefine it for things with phantom record types.
show/hide Instances
SelectField f r a => Select (l f a) (Record r) a
HasField f r => Select (Attr f a) (Rel r) (Expr a)
(#)Source
::
=> Record (RecCons f a RecNil)Rest of record
-> b -> cNew record
-> b -> RecCons f a c
Adds the field from a one-field record to another record.
(<<)Source
::
=> Attr f aExpression
-> e aNew record
-> Record (RecCons f (e a) RecNil)
Creates a record field. Similar to '(.=.)', but gets the field label from an Attr.
(<<-)Source
:: ShowConstant a
=> Attr f aField value
-> aNew record
-> Record (RecCons f (Expr a) RecNil)
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 -> aSource
The (!.) operator selects over returned records from the database (= rows) Non-overloaded version of !. For backwards compatibility.
Relational operators
restrict :: Expr Bool -> Query ()Source
Restricts the records to only those who evaluates the expression to True.
table :: ShowRecRow r => Table r -> Query (Rel r)Source
Return all records from a specific table.
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er)Source
Specifies a subset of the columns in the table.
unique :: Query ()Source
Restricts the relation given to only return unique records. Upshot is all projected attributes will be grouped
union :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)Source
Return all records which are present in at least one of the relations.
intersect :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)Source
Return all records which are present in both relations.
divide :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)Source
Not in SQL92.
minus :: Query (Rel r) -> Query (Rel r) -> Query (Rel r)Source
Return all records from the first relation that are not present in the second relation.
Query expressions
(.==.) :: Eq a => Expr a -> Expr a -> Expr BoolSource
(.==.) 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 BoolSource
(.<>.) 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 BoolSource
As with (.==.) and (.<>.), this op has a standard Haskell op counterpart; (<) and an SQL counterpart; <
(.<=.) :: Ord a => Expr a -> Expr a -> Expr BoolSource
As with (.==.) and (.<>.), this op have a standard Haskell op counterpart, (<=) and an SQL counterpart; <=.
(.>.) :: Ord a => Expr a -> Expr a -> Expr BoolSource
As with (.==.) and (.<>.), this op have a standard Haskell op counterpart, (>) and an SQL counterpart; >.
(.>=.) :: Ord a => Expr a -> Expr a -> Expr BoolSource
As with (.==.) and (.<>.), this op have a standard Haskell op counterpart, (>=) and an SQL counterpart; >=.
(.&&.) :: Expr Bool -> Expr Bool -> Expr BoolSource
"Logical and" on Expr, similar to the (&&) op in Haskell and AND in SQL.
(.||.) :: Expr Bool -> Expr Bool -> Expr BoolSource
"Logical or" on Expr, similar to the (||) op in Haskell and OR in SQL.
(.*.) :: Num a => Expr a -> Expr a -> Expr aSource
Multiplication
(./.) :: Num a => Expr a -> Expr a -> Expr aSource
Division
(.%.) :: Num a => Expr a -> Expr a -> Expr aSource
Modulo
(.+.) :: Num a => Expr a -> Expr a -> Expr aSource
Addition
(.-.) :: Num a => Expr a -> Expr a -> Expr aSource
Subtraction
(.++.) :: Expr String -> Expr String -> Expr StringSource
Concatenates two String-expressions.
_not :: Expr Bool -> Expr BoolSource
The inverse of an Expr Bool.
like :: Expr String -> Expr String -> Expr BoolSource

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 BoolSource
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 StringSource
Produces the concatenation of two String-expressions.
_length :: Expr String -> Expr IntSource
Gets the length of a string.
isNull :: Expr a -> Expr BoolSource
Returns true if the expression is Null.
notNull :: Expr a -> Expr BoolSource
The inverse of isNull, returns false if the expression supplied is Null.
fromNullSource
::
=> Expr aA nullable expression
-> Expr (Maybe a)
-> 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 aSource
Creates a constant expression from a haskell value.
constJust :: ShowConstant a => a -> Expr (Maybe a)Source
Turn constant data into a nullable expression. Same as constant . Just
count :: Expr a -> ExprAggr IntSource
Returns the number of records (=rows) in a query.
_sum :: Num a => Expr a -> ExprAggr aSource
Returns the total sum of a column.
_max :: Ord a => Expr a -> ExprAggr aSource
Returns the highest value of a column.
_min :: Ord a => Expr a -> ExprAggr aSource
Returns the lowest value of a column.
avg :: Num a => Expr a -> ExprAggr aSource
Returns the average of a column.
stddev :: Num a => Expr a -> ExprAggr aSource
Returns the standard deviation of a column.
stddevP :: Num a => Expr a -> ExprAggr aSource
variance :: Num a => Expr a -> ExprAggr aSource
Returns the standard variance of a column.
varianceP :: Num a => Expr a -> ExprAggr aSource
asc :: HasField f r => Rel r -> Attr f a -> OrderExprSource
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 -> OrderExprSource
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 ()Source
Order the results of a query. Use this with the asc or desc functions.
top :: Int -> Query ()Source
Return the n topmost records.
_caseSource
::
=> [(Expr Bool, Expr a)]Else-expression.
-> Expr a
-> 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 aSource
The default value of the column. Only works with insert.
Database operations
data Database Source
query :: GetRec er vr => Database -> Query (Rel er) -> IO [Record vr]Source
performs a query on a database
insert :: (ToPrimExprs r, ShowRecRow r, InsertRec r er) => Database -> Table er -> Record r -> IO ()Source
Inserts a record into a table
deleteSource
:: ShowRecRow r
=> DatabaseThe table to delete records from
-> Table rPredicate used to select records to delete
-> Rel r -> Expr Bool
-> IO ()
deletes a bunch of records
updateSource
:: (ShowLabels s, ToPrimExprs s)
=> DatabaseThe table to update
-> Table rPredicate used to select records to update
-> Rel r -> Expr BoolFunction used to modify selected records
-> Rel r -> Record s
-> IO ()
Updates records
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO ()Source
Inserts values from a query into a table
tablesSource
:: DatabaseDatabase
-> IO [TableName]Names of all tables in the database
List all tables in the database
describeSource
:: DatabaseDatabase
-> TableNameName 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
transactionSource
::
=> DatabaseAction to run
-> IO a
-> IO a
Performs some database action in a transaction. If no exception is thrown, the changes are committed.
Debugging
showQuery :: Query (Rel r) -> StringSource
Shows the optimized PrimQuery.
showQueryUnOpt :: Query (Rel r) -> StringSource
Shows the unoptimized PrimQuery.
showSql :: Query (Rel r) -> StringSource
Shows the optimized SQL query.
showSqlUnOpt :: Query (Rel r) -> StringSource
Shows the unoptimized SQL query.
Produced by Haddock version 2.6.0