grapefruit-records-0.1.0.4: A record system for Functional Reactive Programming

Safe HaskellNone

Data.Record

Contents

Synopsis

Kinds

class Kind kind whereSource

Associated Types

data Forall kind :: (* -> *) -> *Source

Methods

encase :: (forall sort. Sort kind sort => piece sort) -> Forall kind pieceSource

class Sort kind sort whereSource

Methods

specialize :: Forall kind piece -> piece sortSource

Instances

Sort PlainKind val 
Sort SignalKind (Of signal val) 

Styles

class Kind (K style) => Style style Source

Associated Types

type K style :: *Source

Instances

Style PlainStyle 
Style (ConnectorStyle connector) 
Style (SignalStyle era) 
Style style => Style (ContextStyle context style) 

???

type family Value style sort :: *Source

Records

class Kind kind => Record kind record whereSource

The class of all record types.

A record type is a type of records without the style parameter. Therefore, it has kind * -> *.

Methods

build :: thing X -> (forall record name. Record kind record => Forall kind (ExtenderPiece thing record name)) -> thing recordSource

A general method for building record-related “things”.

For each record type, this method constructs a value which is somehow related to this record type. Such a value is called a thing. The type parameter thing maps record types to the types of their corresponding things. The first argument of build gives the thing of the empty record type while the second argument tells how to transform a thing of an arbitrary record type into the thing of this record type extended with an arbitrary field type.

build is used, for example, to implement the function cat.

Instances

Kind kind => Record kind X 
(Kind kind, Record kind record, Sort kind sort) => Record kind (:& record (::: name sort)) 

newtype ExtenderPiece thing record name sort Source

Constructors

ExtenderPiece (thing record -> thing (record :& (name ::: sort))) 

data X style Source

The type of empty records.

Constructors

X 

Instances

OptRecord X 
Subrecord X record 
Kind kind => Record kind X 
Show (X style) 

data (record :& field) style Source

The type of non-empty records, consisting of an initial record and a last field.

Constructors

!(record style) :& !(field style) 

Instances

(Kind kind, Record kind record, Sort kind sort) => Record kind (:& record (::: name sort)) 
OptRecord optRecord => OptRecord (:& optRecord (::: (Opt name) sort)) 
OptRecord optRecord => OptRecord (:& optRecord (::: (Req name) sort)) 
(Dissection record remainder subname subsort, Subrecord subrecord remainder) => Subrecord (:& subrecord (::: subname subsort)) record 
(Show (init style), Show (last style)) => Show (:& init last style) 

data (name ::: sort) style Source

The family of record fields.

Each instance of it matches arbitrary name parameters and all signalOfVal parameters which are of the form signal `Of` val. The actual choice of the instance depends only on the style parameter. The structure of fields of a specific style is documented together with the respective style type.

Constructors

!name := (Value style sort) 

Instances

(Kind kind, Record kind record, Sort kind sort) => Record kind (:& record (::: name sort)) 
OptRecord optRecord => OptRecord (:& optRecord (::: (Opt name) sort)) 
OptRecord optRecord => OptRecord (:& optRecord (::: (Req name) sort)) 
(Dissection record remainder subname subsort, Subrecord subrecord remainder) => Subrecord (:& subrecord (::: subname subsort)) record 
(Show name, Show (Value style sort)) => Show (::: name sort style) 

Catenation

type family Cat record1 record2 :: * -> *Source

The catenation of two record types.

cat :: (Style style, Record (K style) record1, Record (K style) record2) => record1 style -> record2 style -> Cat record1 record2 styleSource

The catenation of two records.

Mapping

map :: (Style style, Style style', K style ~ K style', Record (K style) record) => Forall (K style) (TransformerPiece style style') -> record style -> record style'Source

Application of a function to the fields of a record.

newtype TransformerPiece style style' sort Source

Constructors

TransformerPiece (Value style sort -> Value style' sort) 

Subrecords

class Subrecord subrecord record whereSource

The class of all pairs of record types where the first is a subrecord of the second.

Currenty, the subrecord relation is only defined for records which do not have multiple occurences of the same name. A records is a subrecord of another record if all field types of the first record are also field types of the second, independently of order.

The instance declarations of Subrecord use several helper classes which are hidden. One of them is the class Presence. You get the error message that no instance of Presence name could be found if the alleged subrecord contains a name which is not present in the alleged superrecord.

Methods

narrow :: Style style => record style -> subrecord styleSource

Converts a record into a subrecord by dropping and reordering fields appropriately.

Instances

Subrecord X record 
(Dissection record remainder subname subsort, Subrecord subrecord remainder) => Subrecord (:& subrecord (::: subname subsort)) record