Safe Haskell | None |
---|---|
Language | Haskell2010 |
The HList library
(C) 2004, Oleg Kiselyov, Ralf Laemmel, Keean Schupke
Result-type-driven operations on typeful heterogeneous lists.
- class HOccurrence e1 l l' | e1 l -> l' where
- hOccurrence :: Proxy e1 -> HList l -> HList l'
- class HOccurrence' b e1 l l' | b e1 l -> l' where
- hOccurrence' :: Proxy b -> Proxy e1 -> HList l -> HList l'
- class HOccursMany e l where
- hOccursMany :: HList l -> [e]
- class HOccursMany' e l where
- hOccursMany' :: HList l -> [e]
- hOccursMany1 :: forall e l l'. (HOccurrence e l (e : l'), HOccursMany e l') => HList l -> (e, [e])
- hOccursFst :: forall e l l'. HOccurrence e l (e : l') => HList l -> e
- data TypeNotFound e
- class HOccurs' e l where
- hOccursRest :: (HOccurs l (r v), HDeleteAtLabel * r l v v') => r v -> (l, r v')
- hOccursOpt :: forall e l l'. (HOccurrence e l l', HOccursOpt' e l') => HList l -> Maybe e
- class HOccursOpt' e l where
- hOccursOpt' :: HList l -> Maybe e
- data TypeFound e
- class HOccursNot' b e l
Documentation
class HOccurrence e1 l l' | e1 l -> l' where Source
hOccurrence :: Proxy e1 -> HList l -> HList l' Source
HOccurrence e1 ([] *) ([] *) | |
(HEq * e1 e b, HOccurrence' b e1 ((:) * e l) l') => HOccurrence e1 ((:) * e l) l' |
class HOccurrence' b e1 l l' | b e1 l -> l' where Source
HOccurrence e1 l l' => HOccurrence' False e1 ((:) * e l) l' | |
HOccurrence' True e1 ((:) * e l) ((:) * e l) |
class HOccursMany e l where Source
hOccursMany :: HList l -> [e] Source
(HOccurrence e l l', HOccursMany' e l') => HOccursMany e l |
class HOccursMany' e l where Source
hOccursMany' :: HList l -> [e] Source
HOccursMany' e ([] *) | |
((~) * e e1, HOccursMany e l) => HOccursMany' e ((:) * e1 l) |
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
data TypeNotFound e Source
class HOccurs' e l where Source
Fail * (TypeNotFound * e) => HOccurs' e ([] *) | |
((~) * e e1, HOccursNot * e l) => HOccurs' e ((:) * e l) |
hOccursRest :: (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
class HOccursOpt' e l where Source
hOccursOpt' :: HList l -> Maybe e Source
HOccursOpt' e ([] *) | |
(~) * e e1 => HOccursOpt' e ((:) * e1 l) |
class HOccursNot' b e l Source
HOccursNot * e l => HOccursNot' * False e l | |
Fail * (TypeFound k e) => HOccursNot' k True e l |
Illustration of typical test scenarios
Retrieve the Breed of an animal.
ghci-or-hugs> hOccurs myAnimal :: Breed Cow
Normal hOccurs requires specification of the result type even if the result type is determined by the fact that we are faced with a singleton list.
ghci-or-hugs> hOccurs (HCons 1 HNil) <interactive>:1: No instance for (HOccurs e1 (HCons e HNil))
However, hOccurs can be elaborated as improved as follows:
ghci-or-hugs> hLookup (HCons 1 HNil) 1