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

Portabilitynon-portable
Stabilityexperimental
Maintainer[email protected]
Safe HaskellNone

Database.HaskellDB.HDBRec

Contents

Description

This is a replacement for some of TREX.

Synopsis

Record types

data RecNil Source

The empty record.

Constructors

RecNil 

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 

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 

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) 

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

Arguments

:: l f a

Label

-> a

Value

-> Record (RecCons f a RecNil)

New record

Creates one-field record from a label and a value

(#)Source

Arguments

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

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.

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.

Instances

SelectField f r a => Select (l f a) (Record r) 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.

class SetField f r a Source

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

class RecCat r1 r2 r3 | r1 r2 -> r3 whereSource

Methods

recCat :: r1 -> r2 -> r3Source

Concatenates two records.

Instances

RecCat RecNil r r 
RecCat r1 r2 r3 => RecCat (Record r1) (Record r2) (Record r3) 
RecCat r1 r2 r3 => RecCat (RecCons f a r1) r2 (RecCons f a r3) 

Showing and reading records

class ShowLabels r whereSource

Methods

recordLabels :: r -> [String]Source

class ShowRecRow r whereSource

Convert a record to a list of label names and field values.

Methods

showRecRow :: r -> [(String, ShowS)]Source

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.

Instances

ReadRecRow RecNil 
(FieldTag a, Read b, ReadRecRow c) => ReadRecRow (RecCons a b c)