HList-0.5.0.0: Heterogeneous lists

Safe HaskellNone
LanguageHaskell2010

Data.HList.HOccurs

Contents

Description

The HList library

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

Result-type-driven operations on typeful heterogeneous lists.

Synopsis

Documentation

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

Minimal complete definition

hOccurrence

Methods

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

Instances

HOccurrence e1 ([] *) ([] *) Source # 

Methods

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

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

Methods

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

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

Minimal complete definition

hOccurrence'

Methods

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

Instances

HOccurrence e1 l l' => HOccurrence' False e1 ((:) * e l) l' Source # 

Methods

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

HOccurrence' True e1 ((:) * e l) ((:) * e l) Source # 

Methods

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

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

Minimal complete definition

hOccursMany

Methods

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

Instances

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

Methods

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

class HOccursMany' e l where Source #

Minimal complete definition

hOccursMany'

Methods

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

Instances

HOccursMany' e ([] *) Source # 

Methods

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

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

Methods

hOccursMany' :: HList ((* ': e1) l) -> [e] 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 #

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.

Minimal complete definition

hOccurs'

Methods

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

Instances

Fail ErrorMessage (FieldNotFound * * e (HList l0)) => HOccurs' e ([] *) l0 Source # 

Methods

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

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

Methods

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

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 #

Minimal complete definition

hOccursOpt'

Methods

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

Instances

HOccursOpt' e ([] *) Source # 

Methods

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

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

Methods

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

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

Instances

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 #

Instances

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

Orphan instances

HOccursNot1 k e xs xs => HOccursNot k e xs Source # 
(HOccurs e l, HProject l (HList l')) => HProject l (HList ((:) * e l')) Source # 

Methods

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

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

Methods

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

HProject (HList l) (HList ([] *)) Source # 

Methods

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