HList-0.5.1.0: Heterogeneous lists
Safe HaskellNone
LanguageHaskell2010

Data.HList.HTypeIndexed

Description

The HList library

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

Type-indexed operations on typeful heterogeneous lists.

Synopsis

Documentation

class HType2HNatCase (b :: Bool) (e :: *) (l :: [*]) (n :: HNat) | b e l -> n Source #

Helper class

Instances

Instances details
HOccursNot e l => HType2HNatCase 'True e l 'HZero Source # 
Instance details

Defined in Data.HList.HTypeIndexed

HType2HNat e l n => HType2HNatCase 'False e l ('HSucc n) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

hType2HNat :: HType2HNat e l n => proxy1 e -> proxy l -> Proxy n Source #

hTypes2HNats :: HTypes2HNats es l ns => Proxy (es :: [*]) -> hlist l -> Proxy (ns :: [HNat]) Source #

class HDeleteManyCase (b :: Bool) e1 e l l1 | b e1 e l -> l1 where Source #

Methods

hDeleteManyCase :: Proxy b -> Proxy e1 -> e -> HList l -> HList l1 Source #

Instances

Instances details
HDeleteMany e1 (HList l) (HList l1) => HDeleteManyCase 'False (e1 :: k) e l (e ': l1) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteManyCase :: Proxy 'False -> Proxy e1 -> e -> HList l -> HList (e ': l1) Source #

HDeleteMany e (HList l) (HList l1) => HDeleteManyCase 'True (e :: Type) e l l1 Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteManyCase :: Proxy 'True -> Proxy e -> e -> HList l -> HList l1 Source #

hDeleteAt :: forall (n :: HNat) (l :: [Type]) e proxy1. (HDeleteAtHNat n l, HType2HNat e l n) => proxy1 e -> HList l -> HList (HDeleteAtHNatR n l) Source #

hUpdateAt :: forall (n :: HNat) e (l :: [Type]). (HUpdateAtHNat' n e l l, HType2HNat e l n) => e -> HList l -> HList (HUpdateAtHNatR n e l) Source #

hProjectBy :: forall k (ns :: [HNat]) hlist (l :: k) (z :: [Type]) (es :: [Type]). (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (hlist l, Proxy 'HZero)) z, Apply (FHUProj 'True ns) (hlist l, Proxy 'HZero), HTypes2HNats es l ns) => Proxy es -> hlist l -> HList z Source #

hSplitBy :: forall k (ns :: [HNat]) hlist (l :: k) (z1 :: [Type]) (z2 :: [Type]) (es :: [Type]). (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (hlist l, Proxy 'HZero)) z1, HUnfoldFD (FHUProj 'False ns) (ApplyR (FHUProj 'False ns) (hlist l, Proxy 'HZero)) z2, Apply (FHUProj 'True ns) (hlist l, Proxy 'HZero), Apply (FHUProj 'False ns) (hlist l, Proxy 'HZero), HTypes2HNats es l ns) => Proxy es -> hlist l -> (HList z1, HList z2) Source #

Orphan instances

HDeleteMany (e :: k) (HList ('[] :: [Type])) (HList ('[] :: [Type])) Source # 
Instance details

Methods

hDeleteMany :: Proxy e -> HList '[] -> HList '[] Source #

(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?

Instance details

Methods

hDeleteAtLabel :: Label e -> HList l -> HList l' Source #

(HEq e1 e b, HDeleteManyCase b e1 e l l1) => HDeleteMany (e1 :: Type) (HList (e ': l)) (HList l1) Source # 
Instance details

Methods

hDeleteMany :: Proxy e1 -> HList (e ': l) -> HList l1 Source #

(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

Instance details

HTypes2HNats ('[] :: [Type]) (l :: [Type]) ('[] :: [HNat]) Source #

And lift to the list of types

Instance details

(HType2HNat e l n, HTypes2HNats es l ns) => HTypes2HNats (e ': es :: [Type]) (l :: [Type]) (n ': ns) Source # 
Instance details