| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | haskelldb-users@lists.sourceforge.net |
| Safe Haskell | None |
Database.HaskellDB.DBLayout
Description
Exports every function needed by DBDirect generated files
- module Database.HaskellDB.BoundedString
- module Database.HaskellDB.DBSpec
- data CalendarTime
- data LocalTime
- 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
- 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
- emptyTable :: TableName -> Table (Record RecNil)
Documentation
module Database.HaskellDB.DBSpec
data CalendarTime
Instances
| Eq CalendarTime | |
| Ord CalendarTime | |
| Read CalendarTime | |
| Show CalendarTime | |
| Typeable CalendarTime | |
| ShowConstant CalendarTime | |
| ExprType CalendarTime | |
| GetValue CalendarTime | |
| GetValue (Maybe CalendarTime) |
data LocalTime
Type of normal expressions, contains the untyped 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 |
| (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) |
Basic tables, contains table name and an association from attributes to attribute names in the real table.
Typed attributes
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 |
baseTable :: (ShowLabels r, ToPrimExprs r) => TableName -> Record r -> Table rSource
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.
Instances
| HasField f r => HasField f (RecCons g a r) | |
| HasField f (RecCons f a r) | |
| SetField f r a => SetField f (RecCons g b r) a | |
| SetField f (RecCons f a 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, Show b, ShowRecRow c) => Show (RecCons a b c) | |
| (FieldTag a, Read b, ReadRecRow c) => ReadRecRow (RecCons a b c) | |
| (FieldTag a, Show b, ShowRecRow c) => ShowRecRow (RecCons a b c) | |
| (FieldTag f, ShowLabels r) => ShowLabels (RecCons f a r) | |
| (ExprC e, ToPrimExprs r) => ToPrimExprs (RecCons l (e a) r) | |
| (RelToRec rest, FieldTag f) => RelToRec (RecCons f (Expr a) rest) | |
| (ExprType e, ExprTypes r) => ExprTypes (RecCons f e 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) | |
| (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) |
The empty record.
Instances
| Eq RecNil | |
| Ord RecNil | |
| Read RecNil | |
| Show RecNil | |
| ReadRecRow RecNil | |
| ShowRecRow RecNil | |
| ShowLabels RecNil | |
| ToPrimExprs RecNil | |
| RelToRec RecNil | |
| ExprTypes RecNil | |
| ConstantRecord RecNil RecNil | |
| ProjectRec RecNil RecNil | |
| InsertRec RecNil RecNil | |
| GetRec RecNil RecNil | |
| RecCat RecNil r r | |
| HasField f r => HasField f (Record r) | |
| SetField f r a => SetField f (Record r) a | |
| Eq r => Eq (Record r) | |
| Ord r => Ord (Record r) | |
| ReadRecRow r => Read (Record r) | |
| Show r => Show (Record r) | |
| ShowRecRow r => ShowRecRow (Record r) | |
| ShowLabels r => ShowLabels (Record r) | |
| ExprTypes r => ExprTypes (Record r) | |
| ConstantRecord r cr => ConstantRecord (Record r) (Record cr) | |
| RecCat r1 r2 r3 => RecCat (Record r1) (Record r2) (Record r3) | |
| SelectField f r a => Select (l f a) (Record r) a |
Class for field labels.
Constructs a table entry from a field tag