haskelldb-0.12: SQL unwrapper for Haskell.Source codeContentsIndex
Database.HaskellDB.Query
Portabilitynon portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Contents
Data and class declarations
Operators
Function declarations
Internals
Description
Basic combinators for building type-safe queries. The Query monad constructs a relational expression (PrimQuery).
Synopsis
data Rel r = Rel Alias Scheme
data Attr f a = Attr Attribute
data Table r = Table TableName Assoc
data Query a
data Expr a = Expr PrimExpr
data OrderExpr
class ToPrimExprs r
class ShowConstant a
class ExprC e
class ExprC e => ProjectExpr e
class ProjectRec r er | r -> er
class InsertRec r er | r -> er
class ConstantRecord r cr | r -> cr where
constantRecord :: r -> cr
(.==.) :: 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
(<<) :: Attr f a -> e a -> Record (RecCons f (e a) RecNil)
(<<-) :: ShowConstant a => Attr f a -> a -> Record (RecCons f (Expr a) RecNil)
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er)
restrict :: Expr Bool -> Query ()
table :: ShowRecRow r => Table r -> Query (Rel r)
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)
_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
runQuery :: Query (Rel r) -> PrimQuery
runQueryRel :: Query (Rel r) -> (PrimQuery, Rel r)
attribute :: String -> Expr a
tableName :: Table t -> TableName
baseTable :: (ShowLabels r, ToPrimExprs r) => TableName -> Record r -> Table r
attributeName :: Attr f a -> Attribute
exprs :: ToPrimExprs r => Record r -> [PrimExpr]
labels :: ShowLabels r => r -> [String]
Data and class declarations
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.
Constructors
Rel Alias Scheme
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
Constructors
Attr Attribute
show/hide Instances
HasField f r => Select (Attr f a) (Rel r) (Expr a)
data Table r Source
Basic tables, contains table name and an association from attributes to attribute names in the real table.
Constructors
Table TableName Assoc
data Query a Source
show/hide Instances
data Expr a Source
Type of normal expressions, contains the untyped PrimExpr.
Constructors
Expr 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 OrderExpr Source
show/hide Instances
class ToPrimExprs r Source
show/hide Instances
class ShowConstant a Source
show/hide Instances
class ExprC e Source
Class of expression types.
show/hide Instances
ExprC ExprDefault
ExprC ExprAggr
ExprC Expr
class ExprC e => ProjectExpr e Source
Class of expressions that can be used with project.
show/hide Instances
class ProjectRec r er | r -> erSource
Class of records that can be used with project. All all the values must be instances of ProjectExpr for the record to be an instance of ProjectRec.
show/hide Instances
class InsertRec r er | r -> erSource
Class of records that can be used with insert. All all the values must be instances of InsertExpr for the record to be an instance of InsertRec.
show/hide Instances
InsertRec RecNil RecNil
(InsertExpr e, InsertRec r er) => InsertRec (RecCons f (e a) r) (RecCons f (Expr a) er)
class ConstantRecord r cr | r -> cr whereSource
Methods
constantRecord :: r -> crSource
show/hide Instances
Operators
(.==.) :: 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.
(<<)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
Function declarations
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er)Source
Specifies a subset of the columns in the table.
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.
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.
_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.
Internals
runQuery :: Query (Rel r) -> PrimQuerySource
runQueryRel :: Query (Rel r) -> (PrimQuery, Rel r)Source
attribute :: String -> Expr aSource
tableName :: Table t -> TableNameSource
Get the name of a table.
baseTable :: (ShowLabels r, ToPrimExprs r) => TableName -> Record r -> Table rSource
attributeName :: Attr f a -> AttributeSource
exprs :: ToPrimExprs r => Record r -> [PrimExpr]Source
labels :: ShowLabels r => r -> [String]Source
Produced by Haddock version 2.6.0