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

Safe HaskellSafe
LanguageHaskell98

Data.Record

Contents

Synopsis

Kinds

class Kind kind where Source #

Minimal complete definition

encase

Associated Types

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

Methods

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

Instances

Kind PlainKind Source # 

Associated Types

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

Methods

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

Kind SignalKind Source # 

Associated Types

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

Methods

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

class Sort kind sort where Source #

Minimal complete definition

specialize

Methods

specialize :: Forall kind piece -> piece sort Source #

Instances

Sort PlainKind val Source # 

Methods

specialize :: Forall PlainKind piece -> piece val Source #

Sort SignalKind (Of signal val) Source # 

Methods

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

Styles

class Kind (K style) => Style style Source #

Associated Types

type K style :: * Source #

Instances

Style PlainStyle Source # 

Associated Types

type K PlainStyle :: * Source #

Style (ConnectorStyle connector) Source # 

Associated Types

type K (ConnectorStyle connector) :: * Source #

Style (SignalStyle era) Source # 

Associated Types

type K (SignalStyle era) :: * Source #

Style style => Style (ContextStyle context style) Source # 

Associated Types

type K (ContextStyle context style) :: * Source #

???

type family Value style sort :: * Source #

Instances

type Value PlainStyle val Source # 
type Value PlainStyle val = val
type Value (ConnectorStyle connector) (Of signal val) Source # 
type Value (ConnectorStyle connector) (Of signal val) = connector signal val
type Value (SignalStyle era) (Of signal val) Source # 
type Value (SignalStyle era) (Of signal val) = signal era val
type Value (ContextStyle context style) sort Source # 
type Value (ContextStyle context style) sort = context -> Value style sort

Records

class Kind kind => Record kind record where Source #

The class of all record types.

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

Minimal complete definition

build

Methods

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

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 Source # 

Methods

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

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

Methods

build :: thing X -> (forall record0 name0. Record kind record0 => Forall kind (ExtenderPiece thing record0 name0)) -> thing (record :& (name ::: sort)) Source #

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 Source # 

Associated Types

type All (X :: * -> *) :: * -> * Source #

type Required (X :: * -> *) :: * -> * Source #

Subrecord X record Source # 

Methods

narrow :: Style style => record style -> X style Source #

Kind kind => Record kind X Source # 

Methods

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

Show (X style) Source # 

Methods

showsPrec :: Int -> X style -> ShowS #

show :: X style -> String #

showList :: [X style] -> ShowS #

type All X Source # 
type All X = X
type Required X Source # 
type Required X = X
type Cat record1 X Source # 
type Cat record1 X = record1

data (record :& field) style infixl 2 Source #

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

Constructors

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

Instances

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

Methods

build :: thing X -> (forall record0 name0. Record kind record0 => Forall kind (ExtenderPiece thing record0 name0)) -> thing (record :& (name ::: sort)) Source #

OptRecord optRecord => OptRecord ((:&) optRecord ((:::) (Opt name) sort)) Source # 

Associated Types

type All ((:&) optRecord ((:::) (Opt name) sort) :: * -> *) :: * -> * Source #

type Required ((:&) optRecord ((:::) (Opt name) sort) :: * -> *) :: * -> * Source #

OptRecord optRecord => OptRecord ((:&) optRecord ((:::) (Req name) sort)) Source # 

Associated Types

type All ((:&) optRecord ((:::) (Req name) sort) :: * -> *) :: * -> * Source #

type Required ((:&) optRecord ((:::) (Req name) sort) :: * -> *) :: * -> * Source #

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

Methods

narrow :: Style style => record style -> (subrecord :& (subname ::: subsort)) style Source #

(Show (init style), Show (last style)) => Show ((:&) init last style) Source # 

Methods

showsPrec :: Int -> (init :& last) style -> ShowS #

show :: (init :& last) style -> String #

showList :: [(init :& last) style] -> ShowS #

type Cat record1 ((:&) record2 field2) Source # 
type Cat record1 ((:&) record2 field2) = (:&) (Cat record1 record2) field2
type All ((:&) optRecord ((:::) (Opt name) sort)) Source # 
type All ((:&) optRecord ((:::) (Opt name) sort)) = (:&) (All optRecord) ((:::) name sort)
type All ((:&) optRecord ((:::) (Req name) sort)) Source # 
type All ((:&) optRecord ((:::) (Req name) sort)) = (:&) (All optRecord) ((:::) name sort)
type Required ((:&) optRecord ((:::) (Opt name) sort)) Source # 
type Required ((:&) optRecord ((:::) (Opt name) sort)) = Required optRecord
type Required ((:&) optRecord ((:::) (Req name) sort)) Source # 
type Required ((:&) optRecord ((:::) (Req name) sort)) = (:&) (Required optRecord) ((:::) name sort)

data (name ::: sort) style infix 3 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) infix 3 

Instances

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

Methods

build :: thing X -> (forall record0 name0. Record kind record0 => Forall kind (ExtenderPiece thing record0 name0)) -> thing (record :& (name ::: sort)) Source #

OptRecord optRecord => OptRecord ((:&) optRecord ((:::) (Opt name) sort)) Source # 

Associated Types

type All ((:&) optRecord ((:::) (Opt name) sort) :: * -> *) :: * -> * Source #

type Required ((:&) optRecord ((:::) (Opt name) sort) :: * -> *) :: * -> * Source #

OptRecord optRecord => OptRecord ((:&) optRecord ((:::) (Req name) sort)) Source # 

Associated Types

type All ((:&) optRecord ((:::) (Req name) sort) :: * -> *) :: * -> * Source #

type Required ((:&) optRecord ((:::) (Req name) sort) :: * -> *) :: * -> * Source #

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

Methods

narrow :: Style style => record style -> (subrecord :& (subname ::: subsort)) style Source #

(Show name, Show (Value style sort)) => Show ((:::) name sort style) Source # 

Methods

showsPrec :: Int -> (name ::: sort) style -> ShowS #

show :: (name ::: sort) style -> String #

showList :: [(name ::: sort) style] -> ShowS #

type All ((:&) optRecord ((:::) (Opt name) sort)) Source # 
type All ((:&) optRecord ((:::) (Opt name) sort)) = (:&) (All optRecord) ((:::) name sort)
type All ((:&) optRecord ((:::) (Req name) sort)) Source # 
type All ((:&) optRecord ((:::) (Req name) sort)) = (:&) (All optRecord) ((:::) name sort)
type Required ((:&) optRecord ((:::) (Opt name) sort)) Source # 
type Required ((:&) optRecord ((:::) (Opt name) sort)) = Required optRecord
type Required ((:&) optRecord ((:::) (Req name) sort)) Source # 
type Required ((:&) optRecord ((:::) (Req name) sort)) = (:&) (Required optRecord) ((:::) name sort)

Catenation

type family Cat (record1 :: * -> *) (record2 :: * -> *) :: * -> * Source #

The catenation of two record types.

Instances

type Cat record1 X Source # 
type Cat record1 X = record1
type Cat record1 ((:&) record2 field2) Source # 
type Cat record1 ((:&) record2 field2) = (:&) (Cat record1 record2) field2

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

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 where Source #

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.

Minimal complete definition

narrow

Methods

narrow :: Style style => record style -> subrecord style Source #

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

Instances

Subrecord X record Source # 

Methods

narrow :: Style style => record style -> X style Source #

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

Methods

narrow :: Style style => record style -> (subrecord :& (subname ::: subsort)) style Source #