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

Safe HaskellNone
LanguageHaskell98

Data.Record.Signal

Contents

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

Signal kind

data SignalKind Source #

Instances

Kind SignalKind Source # 

Associated Types

data Forall SignalKind (a :: * -> *) :: * Source #

Methods

encase :: (forall sort. Sort SignalKind sort => piece sort) -> Forall SignalKind piece Source #

Sort SignalKind (Of signal val) Source # 

Methods

specialize :: Forall SignalKind piece -> piece (Of signal val) Source #

data Forall SignalKind Source # 
data Forall SignalKind = SignalForall (forall signal val. func (Of signal val))

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.

Instances

Style (SignalStyle era) Source # 

Associated Types

type K (SignalStyle era) :: * Source #

type K (SignalStyle era) Source # 
type K (SignalStyle era) = SignalKind
type Value (SignalStyle era) (Of signal val) Source # 
type Value (SignalStyle era) (Of signal val) = signal era val

Connector records

type ConsumerRecord record = ConnectorRecord Consumer record Source #

Records which contain signal consumers as values.

type ProducerRecord record = ConnectorRecord Producer record Source #

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.

Instances

Style (ConnectorStyle connector) Source # 

Associated Types

type K (ConnectorStyle connector) :: * Source #

type K (ConnectorStyle connector) Source # 
type K (ConnectorStyle connector) = SignalKind
type Value (ConnectorStyle connector) (Of signal val) Source # 
type Value (ConnectorStyle connector) (Of signal val) = connector signal val

consume :: Record SignalKind 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 SignalKind record => ProducerRecord record -> Circuit era () (SignalRecord era record) Source #

Converts a record of producers into a circuit that produces a corresponding record of signals.