haskelldb-0.12: SQL unwrapper for Haskell.Source codeContentsIndex
Database.HaskellDB.HDBRec
Portabilitynon-portable
Stabilityexperimental
Maintainerhaskelldb-users@lists.sourceforge.net
Contents
Record types
Record construction
Labels
Record predicates and operations
Showing and reading records
Description
This is a replacement for some of TREX.
Synopsis
data RecNil = RecNil
data RecCons f a b = RecCons a b
type Record r = RecNil -> r
emptyRecord :: Record RecNil
(.=.) :: l f a -> a -> Record (RecCons f a RecNil)
(#) :: Record (RecCons f a RecNil) -> (b -> c) -> b -> RecCons f a c
class FieldTag f where
fieldName :: f -> String
class HasField f r
class Select f r a | f r -> a where
(!) :: r -> f -> a
class SetField f r a
setField :: SetField f r a => l f a -> a -> r -> r
class ShowLabels r where
recordLabels :: r -> [String]
class ShowRecRow r where
showRecRow :: r -> [(String, ShowS)]
class ReadRecRow r where
readRecRow :: [(String, String)] -> [(r, [(String, String)])]
Record types
data RecNil Source
The empty record.
Constructors
RecNil
show/hide Instances
data RecCons f a b Source
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.
Constructors
RecCons a b
show/hide 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
SelectField f r a => SelectField f (RecCons g b r) a
SelectField 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)
(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)
type Record r = RecNil -> rSource
The type used for records. This is a function that takes a RecNil so that the user does not have to put a RecNil at the end of every record.
Record construction
emptyRecord :: Record RecNilSource
The empty record
(.=.)Source
::
=> l f aValue
-> aNew record
-> Record (RecCons f a RecNil)
Creates one-field record from a label and a value
(#)Source
::
=> Record (RecCons f a RecNil)Rest of record
-> b -> cNew record
-> b -> RecCons f a c
Adds the field from a one-field record to another record.
Labels
class FieldTag f whereSource
Class for field labels.
Methods
fieldName :: f -> StringSource
Gets the name of the label.
Record predicates and operations
class HasField f r Source
The record r has the field f if there is an instance of HasField f r.
show/hide Instances
HasField f r => HasField f (Record r)
HasField f r => HasField f (RecCons g a r)
HasField f (RecCons f a r)
class Select f r a | f r -> a whereSource
Methods
(!) :: r -> f -> aSource
Field selection operator. It is overloaded so that users (read HaskellDB) can redefine it for things with phantom record types.
show/hide Instances
SelectField f r a => Select (l f a) (Record r) a
HasField f r => Select (Attr f a) (Rel r) (Expr a)
class SetField f r a Source
show/hide Instances
SetField f r a => SetField f (Record r) a
SetField f r a => SetField f (RecCons g b r) a
SetField f (RecCons f a r) a
setField :: SetField f r a => l f a -> a -> r -> rSource
Showing and reading records
class ShowLabels r whereSource
Methods
recordLabels :: r -> [String]Source
show/hide Instances
class ShowRecRow r whereSource
Convert a record to a list of label names and field values.
Methods
showRecRow :: r -> [(String, ShowS)]Source
show/hide Instances
class ReadRecRow r whereSource
Methods
readRecRow :: [(String, String)] -> [(r, [(String, String)])]Source
Convert a list of labels and strins representating values to a record.
show/hide Instances
Produced by Haddock version 2.6.0