grapefruit-records-0.0.0.0: A record systemSource codeContentsIndex
FRP.Grapefruit.Record
Contents
Records
Catenation
Subrecords
Signal records
Connector records
Description

This module provides records of signals and signal-related data.

A record has a type of the following form:

    (X :& name_1 ::: signal_1 `Of` val_1 :& ... :& name_n ::: signal_n `Of` val_n) style

A value of such a type is a list of fields where the ith field has type (name_i ::: signal_i `Of` val_i) style.

(:::) is a data family. Its style parameter is a phantom type which selects the instance of the family. For a concrete style type, the type (name ::: signal `Of` val) style covers name-value pairs where the type of the values depends on signal and val. For example, if style is of the form SignalStyle era, the values have type signal era val. This leads to records of signals with identical era. With the styles Connector Consumer and Connector Producer, it is possible to form records of consumers and producers.

Field names are represented by types which are declared as follows:

    data Name = Name

This makes it possible to use names as types (allowing the use of names in compile-time checks) but also as expressions and patterns.

Synopsis
class Record record where
build :: thing X -> (forall record name signal val. Record record => thing record -> thing (record :& (name ::: (signal `Of` val)))) -> thing record
data X style = X
data (record :& field) style = !(record style) :& !(field style)
data family (name ::: signalOfVal) style :: *
type family Cat record1 record2 :: * -> *
cat :: (Record record1, Record record2) => record1 style -> record2 style -> Cat record1 record2 style
class (Record subrecord, Record record) => Subrecord subrecord record where
narrow :: record style -> subrecord style
type SignalRecord era record = record (SignalStyle era)
data SignalStyle era
type ConsumerRecord record = ConnectorRecord Consumer record
type ProducerRecord record = ConnectorRecord Producer record
type ConnectorRecord connector record = record (ConnectorStyle connector)
data ConnectorStyle connector
consume :: Record record => ConsumerRecord record -> Circuit era (SignalRecord era record) ()
produce :: Record record => ProducerRecord record -> Circuit era () (SignalRecord era record)
Records
class Record 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 signal val. Record record => thing record -> thing (record :& (name ::: (signal `Of` val)))) -> 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.

show/hide Instances
Record X
Record record => Record (record :& (name ::: Of signal val))
data X style Source
The type of empty records.
Constructors
X
show/hide Instances
Record X
OptRecord X
Record record => Subrecord X record
(Present lookupName, Record remainder) => Dissection X remainder lookupName lookupSignal lookupVal
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)
show/hide Instances
Record record => Record (record :& (name ::: Of signal val))
OptRecord optRecord => OptRecord (optRecord :& (Opt name ::: Of signal val))
OptRecord optRecord => OptRecord (optRecord :& (Req name ::: Of signal val))
(Dissection record remainder subname subsignal subval, Subrecord subrecord remainder) => Subrecord (subrecord :& (subname ::: Of subsignal subval)) record
(TypeEq name lookupName namesAreEq, NameMatchDep namesAreEq record name signal val remainder lookupName lookupSignal lookupVal) => Dissection (record :& (name ::: Of signal val)) remainder lookupName lookupSignal lookupVal
data family (name ::: signalOfVal) 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.

Catenation
type family Cat record1 record2 :: * -> *Source
The catenation of two record types.
cat :: (Record record1, Record record2) => record1 style -> record2 style -> Cat record1 record2 styleSource
The catenation of two records.
Subrecords
class (Record subrecord, Record record) => 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 :: record style -> subrecord styleSource
Converts a record into a subrecord by dropping and reordering fields appropriately.
show/hide Instances
Record record => Subrecord X record
(Dissection record remainder subname subsignal subval, Subrecord subrecord remainder) => Subrecord (subrecord :& (subname ::: Of subsignal subval)) record
Signal records
type SignalRecord era record = record (SignalStyle era)Source
Records which contain signals of a common era as values.
data SignalStyle era Source

The style of signal records of a specific era.

Fields of signal style records have the form name ::= signal.

Connector records
type ConsumerRecord record = ConnectorRecord Consumer recordSource
Records which contain signal consumers as values.
type ProducerRecord record = ConnectorRecord Producer recordSource
Records which contain signal producers as values.
type ConnectorRecord connector record = record (ConnectorStyle connector)Source
Records which which contain signal connectors (producers or consumers) as values.
data ConnectorStyle connector Source

The consumer and producer record styles.

ConnectorStyle Consumer is the style of consumer records and ConnectorStyle Producer is the style of producer records. Fields of connector style records have the form name ::~ connector.

consume :: Record record => ConsumerRecord record -> Circuit era (SignalRecord era record) ()Source
Converts a record of consumers into a circuit that consumes a corresponding record of signals.
produce :: Record record => ProducerRecord record -> Circuit era () (SignalRecord era record)Source
Converts a record of producers into a circuit that produces a corresponding record of signals.
Produced by Haddock version 2.4.2