| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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).
- class HExtend e l where- type HExtendR e l
 
- emptyProxy :: Proxy [*] ([] *)
- class SubType l l'
- class HAppend l1 l2 where
- type family HAppendR (l1 :: k) (l2 :: k) :: k
- class HOccurs e l where
- class HOccursNot (e :: k) (l :: [k])
- class HProject l l' where
- class HType2HNat (e :: k) (l :: [k]) (n :: HNat) | e l -> n
- class HTypes2HNats es l (ns :: [HNat]) | es l -> ns
- class HDeleteMany e l l' | e l -> l' where
- class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where
- class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where
- class HUnzip r x y xy => HZip (r :: [*] -> *) x y xy where
Documentation
class HExtend e l where Source #
Minimal complete definition
Instances
| HExtend e (HList l) Source # | |
| HRLabelSet ((:) * t r) => HExtend t (Record r) Source # | |
| ((~) * le (Tagged k l (Maybe e)), HOccursNot * (Label k l) (LabelsOf v)) => HExtend le (Variant v) Source # | Extension for Variants prefers the first value (l .=. Nothing) .*. v = v (l .=. Just e) .*. _ = mkVariant l e Proxy | 
| (HRLabelSet ((:) * (Tagged * e e) l), HTypeIndexed l) => HExtend e (TIP l) Source # | |
| ((~) * me (Maybe e), HOccursNot * (Tagged * e e) l) => HExtend me (TIC l) Source # | Nothing .*. x = x Just a .*. y = mkTIC a | 
| HExtend (Label * (Lbl n ns desc)) (Proxy [Symbol] ((:) Symbol x xs)) Source # | Mixing two label kinds means we have to include  
 | 
| HExtend (Label * (Lbl n ns desc)) (Proxy [*] ((:) * (Lbl n' ns' desc') xs)) Source # | If possible, Label is left off: 
 | 
| HExtend (Label k x) (Proxy [*] ([] *)) Source # | to keep types shorter,  ghc-7.6 does not accept  | 
emptyProxy :: Proxy [*] ([] *) Source #
similar to emptyRecord, emptyTIP, emptyHList (actually called HNil),
 except emptyProxy is the rightmost argument to .*.
class HAppend l1 l2 where Source #
Minimal complete definition
Instances
| HAppendList l1 l2 => HAppend (HList l1) (HList l2) Source # | |
| (HRLabelSet (HAppendListR * r1 r2), HAppend (HList r1) (HList r2)) => HAppend (Record r1) (Record r2) Source # | 
 record .*. field1
       .*. field2 | 
| (HAppend (HList l) (HList l'), HTypeIndexed (HAppendListR * l l')) => HAppend (TIP l) (TIP l') Source # | |
class HOccurs e l where Source #
Minimal complete definition
Instances
| HasField * e (Record ((:) * x ((:) * y l))) e => HOccurs e (TIP ((:) * x ((:) * y l))) Source # | |
| (~) * tee (Tagged * e e) => HOccurs e (TIP ((:) * tee ([] *))) Source # | 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. | 
| (HasField * o (TIC l) mo, (~) * mo (Maybe o)) => HOccurs mo (TIC l) Source # | |
class HOccursNot (e :: k) (l :: [k]) Source #
class HType2HNat (e :: k) (l :: [k]) (n :: HNat) | e l -> n Source #
Map a type (key) to a natural (index) within the collection This is a purely type-level computation
class HTypes2HNats es l (ns :: [HNat]) | es l -> ns Source #
class HDeleteMany e l l' | e l -> l' where Source #
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)
Minimal complete definition
Methods
hDeleteMany :: Proxy e -> l -> l' Source #
class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where Source #
Minimal complete definition
Methods
hDeleteAtLabel :: Label l -> r v -> r v' Source #
Instances
| H2ProjectByLabels ((:) * (Label k l) ([] *)) v t1 v' => HDeleteAtLabel k Record l v v' Source # | |
| (HDeleteAtLabel k Record e v v', HTypeIndexed v') => HDeleteAtLabel k TIP e v v' Source # | |
class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where Source #
Minimal complete definition
Instances
| (SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*])))), HZipList x y xy) => HUnzip HList x y xy Source # | |
| (HZipRecord x y xy, SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*]))))) => HUnzip Record x y xy Source # | |
| (HZipList xL yL xyL, (~) * lty (HList xyL -> (HList xL, HList yL)), Coercible * lty (TIP xy -> (TIP x, TIP y)), (~) [*] (UntagR x) xL, (~) [*] (TagR xL) x, (~) [*] (UntagR y) yL, (~) [*] (TagR yL) y, (~) [*] (UntagR xy) xyL, (~) [*] (TagR xyL) xy, SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*])))), UntagTag x, UntagTag y, UntagTag xy) => HUnzip TIP x y xy Source # | |
| (Unvariant ((:) * txy ([] *)) txy, (~) * tx (Tagged k t x), (~) * ty (Tagged k t y), (~) * txy (Tagged k t (x, y))) => HUnzip Variant ((:) * tx ([] *)) ((:) * ty ([] *)) ((:) * txy ([] *)) Source # | |
| (HUnzip Variant ((:) * x2 xs) ((:) * y2 ys) ((:) * xy2 xys), SameLength * * xs ys, SameLength * * ys xys, (~) * tx (Tagged k t x), (~) * ty (Tagged k t y), (~) * txy (Tagged k t (x, y))) => HUnzip Variant ((:) * tx ((:) * x2 xs)) ((:) * ty ((:) * y2 ys)) ((:) * txy ((:) * xy2 xys)) Source # | |
| HUnzip (Proxy [*]) ([] *) ([] *) ([] *) Source # | |
| ((~) * lv (Tagged k l v), HUnzip (Proxy [*]) ls vs lvs) => HUnzip (Proxy [*]) ((:) * (Label k l) ls) ((:) * v vs) ((:) * lv lvs) Source # | |
class HUnzip r x y xy => HZip (r :: [*] -> *) x y xy where Source #
zip. Variant supports hUnzip, but not hZip (hZipVariant returns a Maybe)
Minimal complete definition
Instances
| (SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*])))), HZipList x y xy) => HZip HList x y xy Source # | |
| (HZipRecord x y xy, SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*]))))) => HZip Record x y xy Source # | 
 | 
| (HUnzip TIP x y xy, HZipList xL yL xyL, (~) * lty (HList xL -> HList yL -> HList xyL), Coercible * lty (TIP x -> TIP y -> TIP xy), (~) [*] (UntagR x) xL, (~) [*] (UntagR y) yL, (~) [*] (UntagR xy) xyL, UntagTag x, UntagTag y, UntagTag xy) => HZip TIP x y xy Source # | |
| HUnzip (Proxy [*]) ls vs lvs => HZip (Proxy [*]) ls vs lvs Source # | Missing from GHC-7.6.3 due to a bug: let r = hEnd $ hBuild 1 2 3
*Data.HList> hZipList r r
H[(1,1),(2,2),(3,3)]
*Data.HList> hZip r r
<interactive>:30:1:
    Couldn't match type `Label k l' with `Integer'
    When using functional dependencies to combine
      HUnzip
        (Proxy [*]) ((':) * (Label k l) ls) ((':) * v vs) ((':) * lv lvs),
        arising from the dependency `xy -> x y'
        in the instance declaration at Data/HList/HListPrelude.hs:96:10
      HUnzip
        HList
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':)
           *
           (Integer, Integer)
           ((':) * (Integer, Integer) ((':) * (Integer, Integer) ('[] *)))),
        arising from a use of `hZip' at <interactive>:30:1-4
    In the expression: hZip r r
    In an equation for `it': it = hZip r r |