haskelldb-0.12: SQL unwrapper for Haskell.Source codeContentsIndex
Database.HaskellDB.PrimQuery
Portabilitynon portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Contents
Type Declarations
Types
Data types
Function declarations
Description
PrimQuery defines the datatype of relational expressions (PrimQuery) and some useful functions on PrimQuery's
Synopsis
type TableName = String
type Attribute = String
type Scheme = [Attribute]
type Assoc = [(Attribute, PrimExpr)]
data PrimQuery
= BaseTable TableName Scheme
| Project Assoc PrimQuery
| Restrict PrimExpr PrimQuery
| Group Assoc PrimQuery
| Binary RelOp PrimQuery PrimQuery
| Special SpecialOp PrimQuery
| Empty
data RelOp
= Times
| Union
| Intersect
| Divide
| Difference
data SpecialOp
= Order [OrderExpr]
| Top Int
data PrimExpr
= AttrExpr Attribute
| BinExpr BinOp PrimExpr PrimExpr
| UnExpr UnOp PrimExpr
| AggrExpr AggrOp PrimExpr
| ConstExpr Literal
| CaseExpr [(PrimExpr, PrimExpr)] PrimExpr
| ListExpr [PrimExpr]
data OrderExpr = OrderExpr OrderOp PrimExpr
data BinOp
= OpEq
| OpLt
| OpLtEq
| OpGt
| OpGtEq
| OpNotEq
| OpAnd
| OpOr
| OpLike
| OpIn
| OpOther String
| OpCat
| OpPlus
| OpMinus
| OpMul
| OpDiv
| OpMod
| OpBitNot
| OpBitAnd
| OpBitOr
| OpBitXor
| OpAsg
data UnOp
= OpNot
| OpIsNull
| OpIsNotNull
| OpLength
| UnOpOther String
data OrderOp
= OpAsc
| OpDesc
data AggrOp
= AggrCount
| AggrSum
| AggrAvg
| AggrMin
| AggrMax
| AggrStdDev
| AggrStdDevP
| AggrVar
| AggrVarP
| AggrOther String
data Literal
= NullLit
| DefaultLit
| BoolLit Bool
| StringLit String
| IntegerLit Integer
| DoubleLit Double
| DateLit CalendarTime
| OtherLit String
extend :: Assoc -> PrimQuery -> PrimQuery
times :: PrimQuery -> PrimQuery -> PrimQuery
attributes :: PrimQuery -> Scheme
attrInExpr :: PrimExpr -> Scheme
attrInOrder :: [OrderExpr] -> Scheme
substAttr :: Assoc -> PrimExpr -> PrimExpr
isAggregate :: PrimExpr -> Bool
foldPrimQuery :: (t, TableName -> Scheme -> t, Assoc -> t -> t, PrimExpr -> t -> t, RelOp -> t -> t -> t, Assoc -> t -> t, SpecialOp -> t -> t) -> PrimQuery -> t
foldPrimExpr :: (Attribute -> t, Literal -> t, BinOp -> t -> t -> t, UnOp -> t -> t, AggrOp -> t -> t, [(t, t)] -> t -> t, [t] -> t) -> PrimExpr -> t
Type Declarations
Types
type TableName = StringSource
type Attribute = StringSource
type Scheme = [Attribute]Source
type Assoc = [(Attribute, PrimExpr)]Source
Data types
data PrimQuery Source
Constructors
BaseTable TableName Scheme
Project Assoc PrimQuery
Restrict PrimExpr PrimQuery
Group Assoc PrimQuery
Binary RelOp PrimQuery PrimQuery
Special SpecialOp PrimQuery
Empty
show/hide Instances
data RelOp Source
Constructors
Times
Union
Intersect
Divide
Difference
show/hide Instances
data SpecialOp Source
Constructors
Order [OrderExpr]
Top Int
show/hide Instances
data PrimExpr Source
Constructors
AttrExpr Attribute
BinExpr BinOp PrimExpr PrimExpr
UnExpr UnOp PrimExpr
AggrExpr AggrOp PrimExpr
ConstExpr Literal
CaseExpr [(PrimExpr, PrimExpr)] PrimExpr
ListExpr [PrimExpr]
show/hide Instances
data OrderExpr Source
Constructors
OrderExpr OrderOp PrimExpr
show/hide Instances
data BinOp Source
Constructors
OpEq
OpLt
OpLtEq
OpGt
OpGtEq
OpNotEq
OpAnd
OpOr
OpLike
OpIn
OpOther String
OpCat
OpPlus
OpMinus
OpMul
OpDiv
OpMod
OpBitNot
OpBitAnd
OpBitOr
OpBitXor
OpAsg
show/hide Instances
data UnOp Source
Constructors
OpNot
OpIsNull
OpIsNotNull
OpLength
UnOpOther String
show/hide Instances
data OrderOp Source
Constructors
OpAsc
OpDesc
show/hide Instances
data AggrOp Source
Constructors
AggrCount
AggrSum
AggrAvg
AggrMin
AggrMax
AggrStdDev
AggrStdDevP
AggrVar
AggrVarP
AggrOther String
show/hide Instances
data Literal Source
Constructors
NullLit
DefaultLitrepresents a default value
BoolLit Bool
StringLit String
IntegerLit Integer
DoubleLit Double
DateLit CalendarTime
OtherLit Stringused for hacking in custom SQL
show/hide Instances
Function declarations
extend :: Assoc -> PrimQuery -> PrimQuerySource
Creates a projection of some attributes while keeping all other attributes in the relation visible too.
times :: PrimQuery -> PrimQuery -> PrimQuerySource
Takes the cartesian product of two queries.
attributes :: PrimQuery -> SchemeSource
Returns the schema (the attributes) of a query
attrInExpr :: PrimExpr -> SchemeSource
Returns all attributes in an expression.
attrInOrder :: [OrderExpr] -> SchemeSource
Returns all attributes in a list of ordering expressions.
substAttr :: Assoc -> PrimExpr -> PrimExprSource
Substitute attribute names in an expression.
isAggregate :: PrimExpr -> BoolSource
foldPrimQuery :: (t, TableName -> Scheme -> t, Assoc -> t -> t, PrimExpr -> t -> t, RelOp -> t -> t -> t, Assoc -> t -> t, SpecialOp -> t -> t) -> PrimQuery -> tSource
Fold on PrimQuery
foldPrimExpr :: (Attribute -> t, Literal -> t, BinOp -> t -> t -> t, UnOp -> t -> t, AggrOp -> t -> t, [(t, t)] -> t -> t, [t] -> t) -> PrimExpr -> tSource
Fold on PrimExpr
Produced by Haddock version 2.6.0