Portability | non portable |
---|---|
Stability | experimental |
Maintainer | "Justin Bailey" <[email protected]> |
Database.HaskellDB
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)
- data Rel r
- data Attr f a
- data Expr a
- data ExprAggr 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)
- copy :: HasField f r => Attr f a -> Rel r -> Record (RecCons f (Expr a) RecNil)
- copyAll :: RelToRec r => Rel r -> Record r
- subQuery :: 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
- fromVal :: ShowConstant a => a -> Expr (Maybe a) -> Expr a
- constant :: ShowConstant a => a -> Expr a
- constVal :: ShowConstant a => a -> Expr (Maybe a)
- constNull :: Expr (Maybe a)
- constExpr :: Expr a -> Expr (Maybe a)
- param :: Expr a -> Expr a
- namedParam :: Name -> Expr a -> Expr a
- class Args a
- func :: Args a => String -> a
- queryParams :: Query (Rel r) -> [Param]
- type Param = Either Int String
- cast :: String -> Expr a -> Expr b
- coerce :: Expr a -> Expr b
- literal :: String -> Expr a
- toStr :: BStrToStr s d => s -> d
- 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]
- recCat :: RecCat r1 r2 r3 => r1 -> r2 -> r3
- 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
Type of relations, contains the attributes
of the relation and an Alias
to which the
attributes are renamed in the PrimQuery
.
Instances
Show (Query (Rel r)) | Shows the optimized SQL for the query. |
ExprTypes r => ExprTypes (Rel r) | |
ExprType a => ExprType (Rel a) | |
HasField f r => Select (Attr f a) (Rel r) (Expr a) | Field selection operator. It is overloaded to work for both
relations in a query and the result of a query.
That is, it corresponds to both |
Typed attributes
Instances
HasField f r => Select (Attr f a) (Rel r) (Expr a) | Field selection operator. It is overloaded to work for both
relations in a query and the result of a query.
That is, it corresponds to both |
Type of normal expressions, contains the untyped PrimExpr.
Instances
ProjectExpr Expr | |
InsertExpr Expr | |
ExprC Expr | |
Read (Expr a) | |
Show (Expr a) | |
IsExpr (Expr a) | |
Args (Expr a) | |
ExprType a => ExprType (Expr a) | |
BStrToStr (Expr String) (Expr String) | |
BStrToStr (Expr (Maybe String)) (Expr (Maybe String)) | |
Size n => BStrToStr (Expr (Maybe (BoundedString n))) (Expr (Maybe String)) | |
Size n => BStrToStr (Expr (BoundedString n)) (Expr String) | |
IsExpr tail => IsExpr (Expr a -> tail) | |
Args (Expr a -> ExprAggr c) | |
(IsExpr tail, Args tail) => Args (Expr a -> tail) | |
HasField f r => Select (Attr f a) (Rel r) (Expr a) | Field selection operator. It is overloaded to work for both
relations in a query and the result of a query.
That is, it corresponds to both |
(RelToRec rest, FieldTag f) => RelToRec (RecCons f (Expr a) rest) | |
(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) |
Type of aggregate expressions.
Basic tables, contains table name and an association from attributes to attribute names in the real table.
Records
The record r
has the field f
if there is an instance of
HasField f r
.
class Select f r a | f r -> a whereSource
Methods
Field selection operator. It is overloaded so that users (read HaskellDB) can redefine it for things with phantom record types.
Instances
SelectField f r a => Select (l f a) (Record r) a | |
HasField f r => Select (Attr f a) (Rel r) (Expr a) | Field selection operator. It is overloaded to work for both
relations in a query and the result of a query.
That is, it corresponds to both |
Arguments
:: 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.
Creates a record field.
Similar to '(.=.)', but gets the field label from an Attr
.
Arguments
:: 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 -> 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.
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er)Source
Specifies a subset of the columns in the table.
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.
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.
copy :: HasField f r => Attr f a -> Rel r -> Record (RecCons f (Expr a) RecNil)Source
Creates a single-field record from an attribute and a table. Useful
for building projections that will re-use the same attribute name. copy attr tbl
is
equivalent to:
attr .=. (tbl .!. attr)
copyAll :: RelToRec r => Rel r -> Record rSource
Copies all columns in the relation given. Useful for appending the remaining columns in a table to a projection. For example:
query = do tbl <- table some_table project $ copyAll tbl
will add all columns in some_table to the query.
subQuery :: Query (Rel r) -> Query (Rel r)Source
Allows a subquery to be created between another query and this query. Normally query definition is associative and query definition is interleaved. This combinator ensures the given query is added as a whole piece.
Query expressions
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.
notNull :: Expr a -> Expr BoolSource
The inverse of isNull
, returns false
if the expression supplied is Null.
Arguments
:: Expr a | Default value (to be returned for |
-> 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
fromVal :: ShowConstant a => a -> Expr (Maybe a) -> Expr aSource
Similar to fromNull, but takes a value argument rather than an Expr.
constant :: ShowConstant a => a -> Expr aSource
Creates a constant expression from a haskell value.
constVal :: ShowConstant a => a -> Expr (Maybe a)Source
Turn constant data into a nullable expression.
Same as constant . Just
constExpr :: Expr a -> Expr (Maybe a)Source
Turn constant data into a nullable expression.
Same as constant . Just
Create an anonymous parameter with a default value.
Create a named parameter with a default value.
Used to implement variable length arguments to func
, below.
func :: Args a => String -> aSource
Can be used to define SQL functions which will appear in queries. Each argument for the function is specified by its own Expr value. Examples include:
lower :: Expr a -> Expr (Maybe String) lower str = func "lower" str
The arguments to the function do not have to be Expr if they can be converted to Expr:
data DatePart = Day | Century deriving Show
datePart :: DatePart -> Expr (Maybe CalendarTime) -> Expr (Maybe Int) datePart date col = func "date_part" (constant $ show date) col
Aggregate functions can also be defined. For example:
every :: Expr Bool -> ExprAggr Bool every col = func "every" col
Aggregates are implemented to always take one argument, so any attempt to define an aggregate with any more or less arguments will result in an error.
Note that type signatures are usually required for each function defined, unless the arguments can be inferred.
queryParams :: Query (Rel r) -> [Param]Source
Get paramaters from a query in order.
type Param = Either Int StringSource
Represents a query parameter. Left parameters are indexed by position, while right parameters are named.
Generates a CAST
expression for the given
expression, using the argument given as the destination
type.
Coerce the type of an expression
to another type. Does not affect the actual
primitive value - only the phantom
type.
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.
Arguments
:: [(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 aSource
The default value of the column. Only works with insert
.
Database operations
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
Arguments
:: 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
Arguments
:: (ShowLabels s, ToPrimExprs s) | |
=> Database | The database |
-> Table r | The table to update |
-> (Rel r -> Expr Bool) | Predicate used to select records to update |
-> (Rel r -> Record s) | Function used to modify selected records |
-> IO () |
Updates records
insertQuery :: ShowRecRow r => Database -> Table r -> Query (Rel r) -> IO ()Source
Inserts values from a query into a table
List all tables in the database
Arguments
:: 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
Performs some database action in a transaction. If no exception is thrown, the changes are committed.
Debugging
showSqlUnOpt :: Query (Rel r) -> StringSource
Shows the unoptimized SQL query.