Safe Haskell | None |
---|
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).
- class HExtend e l where
- class SubType l l'
- class HAppend l1 l2 where
- type family HAppendR l1 l2 :: k
- class HOccurs e l where
- hOccurs :: l -> e
- class HOccursNot e l
- class HProject l l' where
- hProject :: l -> l'
- class HType2HNat e l n | e l -> n
- class HTypes2HNats es l ns | es l -> ns
- class HDeleteMany e l l' | e l -> l' where
- hDeleteMany :: Proxy e -> l -> l'
Documentation
HExtend e (HList l) | |
(HOccursNot * [*] e l, HTypeIndexed l) => HExtend e (TIP l) | |
HRLabelSet (: * (Tagged k l v) r) => HExtend (Tagged k l v) (Record r) |
class HAppend l1 l2 whereSource
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) |
record .*. field1 .*. field2 |
(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
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 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
(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
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)
hDeleteMany :: Proxy e -> l -> l'Source
(HEq * e1 e b, HDeleteManyCase * b e1 e l l1) => HDeleteMany * e1 (HList (: * e l)) (HList l1) | |
HDeleteMany k e (HList ([] *)) (HList ([] *)) |