HList-0.5.1.0: Heterogeneous lists
Safe HaskellNone
LanguageHaskell2010

Data.HList.HOccurs

Description

The HList library

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

Result-type-driven operations on typeful heterogeneous lists.

Synopsis

Documentation

class HOccursNot2 (b :: Bool) e (l :: [k]) (l0 :: [k]) Source #

Instances

Instances details
HOccursNot1 e l l0 => HOccursNot2 'False (e :: k) (l :: [k]) (l0 :: [k]) Source # 
Instance details

Defined in Data.HList.HOccurs

Fail (ExcessFieldFound e l0) => HOccursNot2 'True (e :: k1) (l :: [k2]) (l0 :: [k2]) Source # 
Instance details

Defined in Data.HList.HOccurs

class HOccursNot1 (e :: k) (xs :: [k]) (xs0 :: [k]) Source #

Instances

Instances details
HOccursNot1 (e :: k) ('[] :: [k]) (l0 :: [k]) Source # 
Instance details

Defined in Data.HList.HOccurs

(HEq e e1 b, HOccursNot2 b e l l0) => HOccursNot1 (e :: a) (e1 ': l :: [a]) (l0 :: [a]) Source # 
Instance details

Defined in Data.HList.HOccurs

class HOccursOpt' e l where Source #

Methods

hOccursOpt' :: HList l -> Maybe e Source #

Instances

Instances details
HOccursOpt' e ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursOpt' :: HList '[] -> Maybe e Source #

e ~ e1 => HOccursOpt' e (e1 ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursOpt' :: HList (e1 ': l) -> Maybe e Source #

class HOccurs' e l (l0 :: [*]) where Source #

l0 is the original list so that when we reach the end of l without finding an e, we can report an error that gives an idea about what the original list was.

Methods

hOccurs' :: Proxy l0 -> HList l -> e Source #

Instances

Instances details
Fail (FieldNotFound e (HList l0)) => HOccurs' e ('[] :: [Type]) l0 Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs' :: Proxy l0 -> HList '[] -> e Source #

HOccursNot e l => HOccurs' e (e ': l) l0 Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs' :: Proxy l0 -> HList (e ': l) -> e Source #

class HOccursMany' e l where Source #

Methods

hOccursMany' :: HList l -> [e] Source #

Instances

Instances details
HOccursMany' e ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursMany' :: HList '[] -> [e] Source #

(e ~ e1, HOccursMany e l) => HOccursMany' e (e1 ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursMany' :: HList (e1 ': l) -> [e] Source #

class HOccursMany e (l :: [*]) where Source #

Methods

hOccursMany :: HList l -> [e] Source #

Instances

Instances details
(HOccurrence e l l', HOccursMany' e l') => HOccursMany e l Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursMany :: HList l -> [e] Source #

class HOccurrence' (b :: Bool) (e1 :: *) (l :: [*]) (l' :: [*]) | b e1 l -> l' where Source #

Methods

hOccurrence' :: Proxy b -> Proxy e1 -> HList l -> HList l' Source #

Instances

Instances details
HOccurrence e1 l l' => HOccurrence' 'False e1 (e ': l) l' Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

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

HOccurrence' 'True e1 (e ': l) (e ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurrence' :: Proxy 'True -> Proxy e1 -> HList (e ': l) -> HList (e ': l) Source #

class HOccurrence (e1 :: *) (l :: [*]) (l' :: [*]) | e1 l -> l' where Source #

Methods

hOccurrence :: Proxy e1 -> HList l -> HList l' Source #

Instances

Instances details
HOccurrence e1 ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurrence :: Proxy e1 -> HList '[] -> HList '[] Source #

(HEq e1 e b, HOccurrence' b e1 (e ': l) l') => HOccurrence e1 (e ': l) l' Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

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

hOccursMany1 :: forall e l l'. (HOccurrence e l (e ': l'), HOccursMany e l') => HList l -> (e, [e]) Source #

hOccursFst :: forall e l l'. HOccurrence e l (e ': l') => HList l -> e Source #

hOccursRest :: forall l r (v :: [Type]) (v' :: [Type]). (HOccurs l (r v), HDeleteAtLabel r l v v') => r v -> (l, r v') Source #

lookup a value in the collection (TIP usually) and return the TIP with that element deleted. Used to implement tipyTuple.

hOccursOpt :: forall e l l'. (HOccurrence e l l', HOccursOpt' e l') => HList l -> Maybe e Source #

Orphan instances

HOccursNot1 e xs xs => HOccursNot (e :: k) (xs :: [k]) Source # 
Instance details

(HOccurs e l, HProject l (HList l')) => HProject l (HList (e ': l')) Source # 
Instance details

Methods

hProject :: l -> HList (e ': l') Source #

(HOccurrence e (x ': y) l', HOccurs' e l' (x ': y)) => HOccurs e (HList (x ': y)) Source # 
Instance details

Methods

hOccurs :: HList (x ': y) -> e Source #

HProject (HList l) (HList ('[] :: [Type])) Source # 
Instance details

Methods

hProject :: HList l -> HList '[] Source #