HList-0.3.1.0: Heterogeneous lists

Safe HaskellNone

Data.HList.HListPrelude

Description

The HList library

(C) 2004, Oleg Kiselyov, Ralf Laemmel, Keean Schupke

Declarations for various classes and functions that apply for the whole range of heterogeneous collections (HList, TIP, records, etc).

Synopsis

Documentation

class HExtend e l whereSource

Associated Types

type HExtendR e l Source

Methods

(.*.) :: e -> l -> HExtendR e lSource

Instances

HExtend e (HList l) 
(HOccursNot * [*] e l, HTypeIndexed l) => HExtend e (TIP l) 
HRLabelSet (: * (LVPair k l v) r) => HExtend (LVPair k l v) (Record r) 

class SubType l l' Source

Instances

(HOccurs e (TIP l1), SubType * * (TIP l1) (TIP l2)) => SubType * * (TIP l1) (TIP (: * e l2)) 
SubType * * (TIP l) (TIP ([] *))

Subtyping for TIPs

H2ProjectByLabels k (RecordLabels k r2) r1 r2 rout => SubType * * (Record r1) (Record r2)

Subtyping for records

class HAppend l1 l2 whereSource

Associated Types

type HAppendR l1 l2 Source

Methods

hAppend :: l1 -> l2 -> HAppendR l1 l2Source

Instances

HAppend (HList l1) (HList l2) 
(HAppend (HList l) (HList l'), HTypeIndexed (HAppendList l l')) => HAppend (TIP l) (TIP l') 
(HRLabelSet (HAppendList r1 r2), HAppend (HList r1) (HList r2)) => HAppend (Record r1) (Record r2)
(.*.)
Add a field to a record. Analagous to (++) for lists.
 record .*. field1
        .*. field2

class HOccurs e l whereSource

Methods

hOccurs :: l -> eSource

Instances

(HOccurrence e (: * x y) l', HOccurs' e l') => HOccurs e (HList (: * x y)) 
HOccurs e (HList (: * x (: * y l))) => HOccurs e (TIP (: * x (: * y l))) 
~ * e' e => HOccurs e' (TIP (: * e ([] *)))

One occurrence and nothing is left

This variation provides an extra feature for singleton lists. That is, the result type is unified with the element in the list. Hence the explicit provision of a result type can be omitted.

class HOccursNot e l Source

Instances

HOccursNot k [*] e l => HOccursNot k * e (TIP l) 
HOccursNot k [*] e ([] *) 
(HEq * e e1 b, HOccursNot' * b e l) => HOccursNot * [*] e (: * e1 l) 

class HProject l l' whereSource

Methods

hProject :: l -> l'Source

Instances

(HOccurs e l, HProject l (HList l')) => HProject l (HList (: * e l')) 
HProject (HList l) (HList ([] *)) 

class HType2HNat e l n | e l -> nSource

Map a type (key) to a natural (index) within the collection This is a purely type-level computation

Instances

(HEq * e1 e b, HType2HNatCase b e1 l n) => HType2HNat * [*] e1 (: * e l) n

Map a type to a natural (index within the collection) This is a purely type-level computation

class HTypes2HNats es l ns | es l -> nsSource

Instances

HTypes2HNats [*] [*] ([] *) l ([] HNat)

And lift to the list of types

(HType2HNat k [*] e l n, HTypes2HNats [k] [*] es l ns) => HTypes2HNats [k] [*] (: k e es) l (: HNat n ns) 

class HDeleteMany e l l' | e l -> l' whereSource

Delete all elements with the type-level key e from the collection l. Since the key is type-level, it is represented by a Proxy. (polykinded)

Methods

hDeleteMany :: Proxy e -> l -> l'Source

Instances

(HEq * e1 e b, HDeleteManyCase * b e1 e l l1) => HDeleteMany * e1 (HList (: * e l)) (HList l1) 
HDeleteMany k e (HList ([] *)) (HList ([] *))