HList-0.5.0.0: Heterogeneous lists

Safe HaskellNone
LanguageHaskell2010

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

Minimal complete definition

(.*.)

Associated Types

type HExtendR e l Source #

Methods

(.*.) :: e -> l -> HExtendR e l infixr 2 Source #

Instances

HExtend e (HList l) Source # 

Associated Types

type HExtendR e (HList l) :: * Source #

Methods

(.*.) :: e -> HList l -> HExtendR e (HList l) Source #

HRLabelSet ((:) * t r) => HExtend t (Record r) Source # 

Associated Types

type HExtendR t (Record r) :: * Source #

Methods

(.*.) :: t -> Record r -> HExtendR 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

Associated Types

type HExtendR le (Variant v) :: * Source #

Methods

(.*.) :: le -> Variant v -> HExtendR le (Variant v) Source #

(HRLabelSet ((:) * (Tagged * e e) l), HTypeIndexed l) => HExtend e (TIP l) Source # 

Associated Types

type HExtendR e (TIP l) :: * Source #

Methods

(.*.) :: e -> TIP l -> HExtendR 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

Associated Types

type HExtendR me (TIC l) :: * Source #

Methods

(.*.) :: me -> TIC l -> HExtendR me (TIC l) Source #

HExtend (Label * (Lbl n ns desc)) (Proxy [Symbol] ((:) Symbol x xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]

Associated Types

type HExtendR (Label * (Lbl n ns desc)) (Proxy [Symbol] ((Symbol ': x) xs)) :: * Source #

Methods

(.*.) :: Label * (Lbl n ns desc) -> Proxy [Symbol] ((Symbol ': x) xs) -> HExtendR (Label * (Lbl n ns desc)) (Proxy [Symbol] ((Symbol ': x) xs)) Source #

HExtend (Label * (Lbl n ns desc)) (Proxy [*] ((:) * (Lbl n' ns' desc') xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]

Associated Types

type HExtendR (Label * (Lbl n ns desc)) (Proxy [*] ((* ': Lbl n' ns' desc') xs)) :: * Source #

Methods

(.*.) :: Label * (Lbl n ns desc) -> Proxy [*] ((* ': Lbl n' ns' desc') xs) -> HExtendR (Label * (Lbl n ns desc)) (Proxy [*] ((* ': Lbl n' ns' desc') xs)) Source #

HExtend (Label k x) (Proxy [*] ([] *)) Source #

to keep types shorter, .*. used with Proxy avoids producing a Proxy :: Proxy '[Label x,Label y,Label z] if Proxy :: Proxy '[x,y,z] is not a kind error (as it is when mixing Label6 and Label3 labels).

ghc-7.6 does not accept Proxy ('[] :: [k]) so for now require k ~ *

Associated Types

type HExtendR (Label k x) (Proxy [*] [*]) :: * Source #

Methods

(.*.) :: Label k x -> Proxy [*] [*] -> HExtendR (Label k x) (Proxy [*] [*]) Source #

emptyProxy :: Proxy [*] ([] *) Source #

similar to emptyRecord, emptyTIP, emptyHList (actually called HNil), except emptyProxy is the rightmost argument to .*.

class SubType l l' Source #

Instances

H2ProjectByLabels (LabelsOf r2) r1 r2 rout => SubType * * (Record r1) (Record r2) Source #

Subtyping for records

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

Subtyping for TIPs

class HAppend l1 l2 where Source #

Minimal complete definition

hAppend

Methods

hAppend :: l1 -> l2 -> HAppendR l1 l2 Source #

Instances

HAppendList l1 l2 => HAppend (HList l1) (HList l2) Source # 

Methods

hAppend :: HList l1 -> HList l2 -> HAppendR * (HList l1) (HList l2) Source #

(HRLabelSet (HAppendListR * r1 r2), HAppend (HList r1) (HList r2)) => HAppend (Record r1) (Record r2) Source #
(.*.)
Add a field to a record. Analagous to (++) for lists.
record .*. field1
       .*. field2

Methods

hAppend :: Record r1 -> Record r2 -> HAppendR * (Record r1) (Record r2) Source #

(HAppend (HList l) (HList l'), HTypeIndexed (HAppendListR * l l')) => HAppend (TIP l) (TIP l') Source # 

Methods

hAppend :: TIP l -> TIP l' -> HAppendR * (TIP l) (TIP l') Source #

type family HAppendR (l1 :: k) (l2 :: k) :: k Source #

poly-kinded, but hAppend only works in cases where the kind variable k is *

Instances

type HAppendR * (HList l1) (HList l2) Source # 
type HAppendR * (HList l1) (HList l2) = HList (HAppendListR * l1 l2)
type HAppendR * (Record r1) (Record r2) Source # 
type HAppendR * (Record r1) (Record r2) = Record (HAppendListR * r1 r2)
type HAppendR * (TIP l) (TIP l') Source # 
type HAppendR * (TIP l) (TIP l') = TIP (HAppendListR * l l')

class HOccurs e l where Source #

Minimal complete definition

hOccurs

Methods

hOccurs :: l -> e Source #

Instances

HasField * e (Record ((:) * x ((:) * y l))) e => HOccurs e (TIP ((:) * x ((:) * y l))) Source # 

Methods

hOccurs :: TIP ((* ': x) ((* ': y) l)) -> e 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.

Methods

hOccurs :: TIP ((* ': tee) [*]) -> e Source #

(HasField * o (TIC l) mo, (~) * mo (Maybe o)) => HOccurs mo (TIC l) Source # 

Methods

hOccurs :: TIC l -> mo Source #

class HOccursNot (e :: k) (l :: [k]) Source #

class HProject l l' where Source #

Minimal complete definition

hProject

Methods

hProject :: l -> l' 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

hDeleteMany

Methods

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

class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where Source #

Minimal complete definition

hDeleteAtLabel

Methods

hDeleteAtLabel :: Label l -> r v -> r v' Source #

Instances

H2ProjectByLabels ((:) * (Label k l) ([] *)) v t1 v' => HDeleteAtLabel k Record l v v' Source # 

Methods

hDeleteAtLabel :: Label Record v -> l v' -> l v' Source #

(HDeleteAtLabel k Record e v v', HTypeIndexed v') => HDeleteAtLabel k TIP e v v' Source # 

Methods

hDeleteAtLabel :: Label TIP v -> e v' -> e v' Source #

class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where Source #

Minimal complete definition

hUnzip

Methods

hUnzip :: r xy -> (r x, r y) Source #

Instances

(SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*])))), HZipList x y xy) => HUnzip HList x y xy Source # 

Methods

hUnzip :: HList xy -> (HList x, HList y) Source #

(HZipRecord x y xy, SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*]))))) => HUnzip Record x y xy Source # 

Methods

hUnzip :: Record xy -> (Record x, Record y) 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 # 

Methods

hUnzip :: TIP xy -> (TIP x, TIP y) 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 # 

Methods

hUnzip :: Variant ((* ': txy) [*]) -> (Variant ((* ': tx) [*]), Variant ((* ': ty) [*])) 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 # 

Methods

hUnzip :: Variant ((* ': txy) ((* ': xy2) xys)) -> (Variant ((* ': tx) ((* ': x2) xs)), Variant ((* ': ty) ((* ': y2) ys))) Source #

HUnzip (Proxy [*]) ([] *) ([] *) ([] *) Source # 

Methods

hUnzip :: Proxy [*] [*] -> (Proxy [*] [*], Proxy [*] [*]) Source #

((~) * lv (Tagged k l v), HUnzip (Proxy [*]) ls vs lvs) => HUnzip (Proxy [*]) ((:) * (Label k l) ls) ((:) * v vs) ((:) * lv lvs) Source # 

Methods

hUnzip :: Proxy [*] ((* ': lv) lvs) -> (Proxy [*] ((* ': Label k l) ls), Proxy [*] ((* ': v) vs)) 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

hZip

Methods

hZip :: r x -> r y -> r xy Source #

Instances

(SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*])))), HZipList x y xy) => HZip HList x y xy Source # 

Methods

hZip :: HList x -> HList y -> HList xy Source #

(HZipRecord x y xy, SameLengths * ((:) [*] x ((:) [*] y ((:) [*] xy ([] [*]))))) => HZip Record x y xy Source #
>>> let x :: Record '[Tagged "x" Int]; x = undefined
>>> let y :: Record '[Tagged "x" Char]; y = undefined
>>> :t hZip x y
hZip x y :: Record '[Tagged "x" (Int, Char)]

Methods

hZip :: Record x -> Record y -> Record 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 # 

Methods

hZip :: TIP x -> TIP y -> TIP 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

Methods

hZip :: Proxy [*] ls -> Proxy [*] vs -> Proxy [*] lvs Source #