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
- class HOccurrence' (b :: Bool) (e1 :: *) (l :: [*]) (l' :: [*]) | b e1 l -> l' where
- class HOccursMany e (l :: [*]) where
- class HOccursMany' e l where
- 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 (l0 :: [*]) where
- hOccursRest :: (HDeleteAtLabel * r l v v', HOccurs l (r 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
- class HOccursNot1 (e :: k) (xs :: [k]) (xs0 :: [k])
- class HOccursNot2 (b :: Bool) e (l :: [k]) (l0 :: [k])
Documentation
class HOccurrence (e1 :: *) (l :: [*]) (l' :: [*]) | e1 l -> l' where Source #
HOccurrence e1 ([] *) ([] *) Source # | |
(HEq * e1 e b, HOccurrence' b e1 ((:) * e l) l') => HOccurrence e1 ((:) * e l) l' Source # | |
class HOccurrence' (b :: Bool) (e1 :: *) (l :: [*]) (l' :: [*]) | b e1 l -> l' where Source #
HOccurrence e1 l l' => HOccurrence' False e1 ((:) * e l) l' Source # | |
HOccurrence' True e1 ((:) * e l) ((:) * e l) Source # | |
class HOccursMany e (l :: [*]) where Source #
hOccursMany :: HList l -> [e] Source #
(HOccurrence e l l', HOccursMany' e l') => HOccursMany e l Source # | |
class HOccursMany' e l where Source #
hOccursMany' :: HList l -> [e] Source #
HOccursMany' e ([] *) Source # | |
((~) * e e1, HOccursMany e l) => HOccursMany' e ((:) * e1 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 #
data TypeNotFound 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.
hOccursRest :: (HDeleteAtLabel * r l v v', HOccurs l (r 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 ([] *) Source # | |
(~) * e e1 => HOccursOpt' e ((:) * e1 l) Source # | |
class HOccursNot1 (e :: k) (xs :: [k]) (xs0 :: [k]) Source #
HOccursNot1 k e ([] k) l0 Source # | |
(HEq a e e1 b, HOccursNot2 a a b e l l0) => HOccursNot1 a e ((:) a e1 l) l0 Source # | |
class HOccursNot2 (b :: Bool) e (l :: [k]) (l0 :: [k]) Source #
HOccursNot1 k e l l0 => HOccursNot2 k k False e l l0 Source # | |
Fail ErrorMessage (ExcessFieldFound k2 [k1] e l0) => HOccursNot2 k2 k1 True e l l0 Source # | |
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