Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- class HExtend e l where
- emptyProxy :: Proxy ('[] :: [Type])
- class SubType l l'
- class HAppend l1 l2 where
- type family HAppendR (l1 :: k) (l2 :: k) :: k
- class HOccurs e l where
- hOccurs :: l -> e
- class HOccursNot (e :: k) (l :: [k])
- class HProject l l' where
- hProject :: l -> l'
- 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
- hDeleteMany :: Proxy e -> l -> l'
- class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where
- hDeleteAtLabel :: Label l -> r v -> r v'
- class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where
- hUnzip :: r xy -> (r x, r y)
- class HUnzip r x y xy => HZip (r :: [*] -> *) x y xy where
- hZip :: r x -> r y -> r xy
Documentation
class HExtend e l where Source #
Instances
HExtend e (HList l) Source # | |
(HRLabelSet (Tagged e e ': l), HTypeIndexed l) => HExtend e (TIP l) Source # | |
(le ~ Tagged l (Maybe e), HOccursNot (Label 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 |
(me ~ Maybe e, HOccursNot (Tagged e e) l) => HExtend me (TIC l) Source # | Nothing .*. x = x Just a .*. y = mkTIC a |
HRLabelSet (t ': r) => HExtend t (Record r) Source # | |
HExtend (Label y) (Proxy (x ': xs)) Source # | |
HExtend (Label y) (Proxy (x ': xs)) Source # | |
HExtend (Label y) (Proxy (x ': xs)) Source # | |
HExtend (Label y) (Proxy (x ': xs)) Source # | |
HExtend (Label y) (Proxy (x ': xs)) Source # |
|
HExtend (Label y) (Proxy (x ': xs)) Source # | Mixing two label kinds means we have to include
|
HExtend (Label (Lbl n ns desc)) (Proxy (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 x) (Proxy ('[] :: [Type])) Source # | to keep types shorter, ghc-7.6 does not accept |
(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (x ': xs)) Source # | |
(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (Lbl n ns desc ': xs)) Source # | if the proxy has Data.HList.Label3.Lbl, then everything has to be wrapped in Label to make the kinds match up. |
(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy ('[] :: [Type])) Source # | Together with the instance below, this allows writing
Or with HListPP p = `x .*. `y .*. `z .*. emptyProxy instead of p = Proxy :: Proxy ["x","y","z"] |
emptyProxy :: Proxy ('[] :: [Type]) Source #
similar to emptyRecord
, emptyTIP
, emptyHList (actually called HNil
),
except emptyProxy is the rightmost argument to .*.
Instances
H2ProjectByLabels (LabelsOf r2) r1 r2 rout => SubType (Record r1 :: Type) (Record r2 :: Type) Source # | Subtyping for records |
Defined in Data.HList.Record | |
SubType (TIP l :: Type) (TIP ('[] :: [Type])) Source # | Subtyping for TIPs |
Defined in Data.HList.TIP | |
(HOccurs e (TIP l1), SubType (TIP l1) (TIP l2)) => SubType (TIP l1 :: Type) (TIP (e ': l2) :: Type) Source # | |
Defined in Data.HList.TIP |
class HAppend l1 l2 where Source #
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 #
Instances
(HOccurrence e (x ': y) l', HOccurs' e l' (x ': y)) => HOccurs e (HList (x ': y)) Source # | |
Defined in Data.HList.HOccurs | |
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. |
Defined in Data.HList.TIP | |
HasField e (Record (x ': (y ': l))) e => HOccurs e (TIP (x ': (y ': l))) Source # | |
Defined in Data.HList.TIP | |
(HasField o (TIC l) mo, mo ~ Maybe o) => HOccurs mo (TIC l) Source # | |
Defined in Data.HList.TIC |
class HOccursNot (e :: k) (l :: [k]) Source #
Instances
HOccursNot1 e xs xs => HOccursNot (e :: k) (xs :: [k]) Source # | |
Defined in Data.HList.HOccurs |
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
Instances
(HEq e1 e b, HType2HNatCase b e1 l n) => HType2HNat (e1 :: Type) (e ': l :: [Type]) n Source # | Map a type to a natural (index within the collection) This is a purely type-level computation |
Defined in Data.HList.HTypeIndexed |
class HTypes2HNats es l (ns :: [HNat]) | es l -> ns Source #
Instances
HTypes2HNats ('[] :: [Type]) (l :: [Type]) ('[] :: [HNat]) Source # | And lift to the list of types |
Defined in Data.HList.HTypeIndexed | |
(HType2HNat e l n, HTypes2HNats es l ns) => HTypes2HNats (e ': es :: [Type]) (l :: [Type]) (n ': ns) Source # | |
Defined in Data.HList.HTypeIndexed |
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)
hDeleteMany :: Proxy e -> l -> l' Source #
Instances
(HEq e1 e b, HDeleteManyCase b e1 e l l1) => HDeleteMany (e1 :: Type) (HList (e ': l)) (HList l1) Source # | |
Defined in Data.HList.HTypeIndexed | |
HDeleteMany (e :: k) (HList ('[] :: [Type])) (HList ('[] :: [Type])) Source # | |
Defined in Data.HList.HTypeIndexed |
class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where Source #
hDeleteAtLabel :: Label l -> r v -> r v' Source #
Instances
(HDeleteAtHNat n l, HType2HNat e l n, l' ~ HDeleteAtHNatR n l) => HDeleteAtLabel HList (e :: Type) l l' Source # | should this instead delete the first element of that type? |
Defined in Data.HList.HTypeIndexed | |
H2ProjectByLabels '[Label l] v t1 v' => HDeleteAtLabel Record (l :: k) v v' Source # | |
Defined in Data.HList.Record | |
(HDeleteAtLabel Record e v v', HTypeIndexed v') => HDeleteAtLabel TIP (e :: k) v v' Source # | |
Defined in Data.HList.TIP |
class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where Source #
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 # | |
(HUnzip Variant (x2 ': xs) (y2 ': ys) (xy2 ': xys), SameLength xs ys, SameLength ys xys, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant (tx ': (x2 ': xs)) (ty ': (y2 ': ys)) (txy ': (xy2 ': xys)) Source # | |
(Unvariant '[txy] txy, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant '[tx] '[ty] '[txy] Source # | |
HUnzip (Proxy :: [Type] -> Type) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # | |
(lv ~ Tagged l v, HUnzip (Proxy :: [Type] -> Type) ls vs lvs) => HUnzip (Proxy :: [Type] -> Type) (Label 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)
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 :: [Type] -> Type) ls vs lvs => HZip (Proxy :: [Type] -> Type) 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 |