|
Database.HaskellDB.Query | Portability | non portable | Stability | experimental | Maintainer | haskelldb-users@lists.sourceforge.net |
|
|
|
|
|
Description |
Basic combinators for building type-safe queries.
The Query monad constructs a relational expression
(PrimQuery).
|
|
Synopsis |
|
|
|
|
Data and class declarations
|
|
data Rel r |
Type of relations, contains the attributes
of the relation and an Alias to which the
attributes are renamed in the PrimQuery.
| Constructors | | Instances | |
|
|
data Attr f a |
Typed attributes
| Constructors | | Instances | |
|
|
data Table r |
Basic tables, contains table name and an
association from attributes to attribute
names in the real table.
| Constructors | |
|
|
data Query a |
Instances | |
|
|
data Expr a |
Type of normal expressions, contains the untyped PrimExpr.
| Constructors | | Instances | |
|
|
data OrderExpr |
Instances | |
|
|
class ToPrimExprs r |
| Instances | |
|
|
class ShowConstant a |
| Instances | |
|
|
class ExprC e |
Class of expression types.
| | Instances | |
|
|
class ExprC e => ProjectExpr e |
Class of expressions that can be used with project.
| | Instances | |
|
|
class ProjectRec r er | r -> er |
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.
| | Instances | |
|
|
class InsertRec r er | r -> er |
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.
| | Instances | |
|
|
class ConstantRecord r cr | r -> cr where |
| Methods | constantRecord :: r -> cr |
| | Instances | |
|
|
Operators
|
|
(.==.) :: 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.
|
|
(<<) |
:: 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
|
|
|
Function declarations
|
|
project :: (ShowLabels r, ToPrimExprs r, ProjectRec r er) => Record r -> Query (Rel er) |
Specifies a subset of the columns in the table.
|
|
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.
|
|
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.
|
|
_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.
|
|
Internals
|
|
runQuery :: Query (Rel r) -> PrimQuery |
|
runQueryRel :: Query (Rel r) -> (PrimQuery, Rel r) |
|
attribute :: String -> Expr a |
|
tableName :: Table t -> TableName |
Get the name of a table.
|
|
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] |
|
Produced by Haddock version 0.8 |