haskelldb-0.10: SQL unwrapper for Haskell.ContentsIndex
Database.HaskellDB.DBLayout
Portabilitynon-portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Description
Exports every function needed by DBDirect generated files
Synopsis
module Database.HaskellDB.BoundedString
module Database.HaskellDB.DBSpec
data Expr a
data Table r
data Attr f a
baseTable :: (ShowLabels r, ToPrimExprs r) => TableName -> Record r -> Table r
data RecCons f a b
data RecNil
class FieldTag f where
fieldName :: f -> String
fieldName :: FieldTag f => f -> String
hdbMakeEntry :: FieldTag f => f -> Record (RecCons f (Expr a) RecNil)
mkAttr :: FieldTag f => f -> Attr f a
(#) :: Record (RecCons f a RecNil) -> (b -> c) -> (b -> RecCons f a c)
Documentation
module Database.HaskellDB.BoundedString
module Database.HaskellDB.DBSpec
data Expr a
Type of normal expressions, contains the untyped PrimExpr.
show/hide Instances
ExprC Expr
InsertExpr Expr
ProjectExpr Expr
Read (Expr a)
Show (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)
(GetValue a, GetRec er vr) => GetRec (RecCons f (Expr a) er) (RecCons f a vr)
(InsertExpr e, InsertRec r er) => InsertRec (RecCons f (e a) r) (RecCons f (Expr a) er)
(ProjectExpr e, ProjectRec r er) => ProjectRec (RecCons f (e a) r) (RecCons f (Expr a) er)
data Table r
Basic tables, contains table name and an association from attributes to attribute names in the real table.
data Attr f a
Typed attributes
show/hide Instances
HasField f r => Select (Attr f a) (Rel r) (Expr a)
baseTable :: (ShowLabels r, ToPrimExprs r) => TableName -> Record r -> Table r
data RecCons f a b
Constructor that adds a field to a record. f is the field tag, a is the field value and b is the rest of the record.
show/hide Instances
HasField f (RecCons f a r)
HasField f r => HasField f (RecCons g a r)
SelectField f (RecCons f a r) a
SelectField f r a => SelectField f (RecCons g b r) a
SetField f (RecCons f a r) a
SetField f r a => SetField f (RecCons g b r) a
(Eq a, Eq b) => Eq (RecCons f a b)
(Ord a, Ord b) => Ord (RecCons f a b)
(FieldTag a, Read b, ReadRecRow c) => Read (RecCons a b c)
(FieldTag a, Read b, ReadRecRow c) => ReadRecRow (RecCons a b c)
(FieldTag a, Show b, ShowRecRow c) => Show (RecCons a b c)
(FieldTag f, ShowLabels r) => ShowLabels (RecCons f a r)
(FieldTag a, Show b, ShowRecRow c) => ShowRecRow (RecCons a b c)
(ExprC e, ToPrimExprs r) => ToPrimExprs (RecCons l (e a) r)
RecCat r1 r2 r3 => RecCat (RecCons f a r1) r2 (RecCons f a r3)
(ShowConstant a, ConstantRecord r cr) => ConstantRecord (RecCons f a r) (RecCons f (Expr a) cr)
(GetValue a, GetRec er vr) => GetRec (RecCons f (Expr a) er) (RecCons f a vr)
(InsertExpr e, InsertRec r er) => InsertRec (RecCons f (e a) r) (RecCons f (Expr a) er)
(ProjectExpr e, ProjectRec r er) => ProjectRec (RecCons f (e a) r) (RecCons f (Expr a) er)
data RecNil
The empty record.
show/hide Instances
class FieldTag f where
Class for field labels.
Methods
fieldName :: f -> String
Gets the name of the label.
fieldName :: FieldTag f => f -> String
Gets the name of the label.
hdbMakeEntry
:: FieldTag f
=> fField tag
-> Record (RecCons f (Expr a) RecNil)
Constructs a table entry from a field tag
mkAttr
:: FieldTag f
=> fField tag
-> Attr f a
Make an Attr for a field.
(#)
:: 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.
Produced by Haddock version 0.8