haskelldb-2.2.4: A library of combinators for generating and executing SQL statements.

CopyrightDaan Leijen (c) 1999, daan@cs.uu.nl HWT Group (c) 2003, haskelldb-users@lists.sourceforge.net
LicenseBSD-style
Maintainerhaskelldb-users@lists.sourceforge.net
Stabilityexperimental
Portabilitynon portable
Safe HaskellNone
LanguageHaskell98

Database.HaskellDB.Query

Contents

Description

Basic combinators for building type-safe queries. The Query monad constructs a relational expression (PrimQuery).

Synopsis

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 

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 ! and !. from the original HaskellDB. An overloaded operator was selected because users (and the developers) always forgot to use !. instead of ! on query results.

data Attr f a Source

Typed attributes

Constructors

Attr Attribute 

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 ! and !. from the original HaskellDB. An overloaded operator was selected because users (and the developers) always forgot to use !. instead of ! on query results.

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

Instances

Monad Query 
Functor Query 
Applicative Query 
Show (Query (Rel r))

Shows the optimized SQL for the query.

newtype Expr a Source

Type of normal expressions, contains the untyped PrimExpr.

Constructors

Expr PrimExpr 

Instances

ProjectExpr Expr 
ExprC Expr 
Read (Expr a) 
Show (Expr a) 
Args (Expr a) 
ExprType a => ExprType (Expr a) 
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 ! and !. from the original HaskellDB. An overloaded operator was selected because users (and the developers) always forgot to use !. instead of ! on query results.

(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) 

class ToPrimExprs r Source

Minimal complete definition

toPrimExprs

Instances

class ConstantRecord r cr | r -> cr where Source

Converts records w/o Expr (usually from database queries) to records with Expr types.

Methods

constantRecord :: r -> cr Source

class ExprC e where Source

Class of expression types.

Methods

primExpr :: e a -> PrimExpr Source

Get the underlying untyped PrimExpr.

class ExprC e => ProjectExpr e Source

Class of expressions that can be used with project.

class ProjectRec r er | r -> er Source

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 Source

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

InsertRec RecNil RecNil 
(InsertExpr e, InsertRec r er) => InsertRec (RecCons f (e a) r) (RecCons f (Expr a) er) 

newtype ExprAggr a Source

Type of aggregate expressions.

Constructors

ExprAggr PrimExpr 

newtype ExprDefault a Source

The type of default expressions.

Constructors

ExprDefault PrimExpr 

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 r Source

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.

class RelToRec a Source

Helper class which gives a polymorphic copy function that can turn a Rel into a Record.

Minimal complete definition

relToRec

Instances

RelToRec RecNil 
(RelToRec rest, FieldTag f) => RelToRec (RecCons f (Expr a) rest) 

Operators

(.==.) :: Eq a => Expr a -> Expr a -> Expr Bool infix 4 Source

Equality comparison on Exprs, = in SQL.

(.<>.) :: Eq a => Expr a -> Expr a -> Expr Bool infix 4 Source

Inequality on Exprs, <> in SQL.

(.<.) :: Ord a => Expr a -> Expr a -> Expr Bool infix 4 Source

(.<=.) :: Ord a => Expr a -> Expr a -> Expr Bool infix 4 Source

(.>.) :: Ord a => Expr a -> Expr a -> Expr Bool infix 4 Source

(.>=.) :: Ord a => Expr a -> Expr a -> Expr Bool infix 4 Source

(.&&.) :: Expr Bool -> Expr Bool -> Expr Bool infixr 3 Source

"Logical and" on Expr, AND in SQL.

(.||.) :: Expr Bool -> Expr Bool -> Expr Bool infixr 2 Source

"Logical or" on Expr. OR in SQL.

(.*.) :: Num a => Expr a -> Expr a -> Expr a infixl 7 Source

Multiplication

(./.) :: Num a => Expr a -> Expr a -> Expr a infixl 7 Source

Division

(.+.) :: Num a => Expr a -> Expr a -> Expr a infixl 6 Source

Addition

(.-.) :: Num a => Expr a -> Expr a -> Expr a infixl 6 Source

Subtraction

(.%.) :: Num a => Expr a -> Expr a -> Expr a infixl 7 Source

Modulo

(.++.) :: Expr String -> Expr String -> Expr String infixr 5 Source

Concatenates two String-expressions.

(<<) infix 6 Source

Arguments

:: 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.

(<<-) infix 6 Source

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

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.

unionAll :: Query (Rel r) -> Query (Rel r) -> Query (Rel r) Source

UNION ALL

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 Bool Source

The inverse of an Expr Bool.

like :: Expr String -> Expr String -> Expr Bool infix 8 Source

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 infix 8 Source

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 Source

Produces the concatenation of two String-expressions.

_length :: Expr String -> Expr Int Source

Gets the length of a string.

isNull :: Expr a -> Expr Bool Source

Returns true if the expression is Null.

notNull :: Expr a -> Expr Bool Source

The inverse of isNull, returns false if the expression supplied is Null.

fromNull Source

Arguments

:: 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

fromVal :: ShowConstant a => a -> Expr (Maybe a) -> Expr a Source

Similar to fromNull, but takes a value argument rather than an Expr.

constant :: ShowConstant a => a -> Expr a Source

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

constNull :: Expr (Maybe a) Source

Represents a null value.

constExpr :: Expr a -> Expr (Maybe a) Source

Turn constant data into a nullable expression. Same as constant . Just

param Source

Arguments

:: Expr a

Default value.

-> Expr a 

Create an anonymous parameter with a default value.

namedParam Source

Arguments

:: Name

Name of the parameter.

-> Expr a

Default value for the parameter.

-> Expr a 

Create a named parameter with a default value.

class Args a Source

Used to implement variable length arguments to func, below.

Minimal complete definition

arg_

Instances

Args (Expr a) 
Args (Expr a -> ExprAggr c) 
(IsExpr tail, Args tail) => Args (Expr a -> tail) 

func :: Args a => String -> a Source

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.

cast Source

Arguments

:: String

Destination type.

-> Expr a

Source expression.

-> Expr b 

Generates a CAST expression for the given expression, using the argument given as the destination type.

toStr :: BStrToStr s d => s -> d Source

Convert a bounded string to a real string.

coerce Source

Arguments

:: Expr a

Source expression

-> Expr b

Destination type.

Coerce the type of an expression to another type. Does not affect the actual primitive value - only the phantom type.

select :: HasField f r => Attr f a -> Rel r -> Expr a Source

count :: Expr a -> ExprAggr Int Source

Returns the number of records (=rows) in a query.

_sum :: Num a => Expr a -> ExprAggr a Source

Returns the total sum of a column.

_max :: Ord a => Expr a -> ExprAggr a Source

Returns the highest value of a column.

_min :: Ord a => Expr a -> ExprAggr a Source

Returns the lowest value of a column.

avg :: Num a => Expr a -> ExprAggr a Source

Returns the average of a column.

literal :: String -> Expr a Source

Inserts the string literally - no escaping, no quoting.

stddev :: Num a => Expr a -> ExprAggr a Source

Returns the standard deviation of a column.

stddevP :: Num a => Expr a -> ExprAggr a Source

variance :: Num a => Expr a -> ExprAggr a Source

Returns the standard variance of a column.

asc :: HasField f r => Rel r -> Attr f a -> OrderExpr Source

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 Source

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.

offset :: Int -> Query () Source

Skip the n topmost records.

_case Source

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 a Source

The default value of the column. Only works with insert.

Internals

unQuery :: Query a -> a Source

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.

tableName :: Table t -> TableName Source

Get the name of a table.

emptyTable :: TableName -> Table (Record RecNil) Source

For queries against fake tables, such as 'information_schema.information_schema_catalog_name'. Useful for constructing queries that contain constant data (and do not select from columns) but need a table to select from.