module Data.HList.HOccurs (
module Data.HList.HOccurs,
) where
import Data.HList.FakePrelude
import Data.HList.HListPrelude
import Data.HList.HList
class HOccurrence (e1 :: *) (l :: [*]) (l' :: [*]) | e1 l -> l' where
hOccurrence :: Proxy e1 -> HList l -> HList l'
instance HOccurrence e1 '[] '[] where
hOccurrence _ = id
instance (HEq e1 e b, HOccurrence' b e1 (e ': l) l')
=> HOccurrence e1 (e ': l) l' where
hOccurrence = hOccurrence' (Proxy::Proxy b)
class HOccurrence' (b :: Bool) (e1 :: *) (l :: [*]) (l' :: [*]) | b e1 l -> l' where
hOccurrence' :: Proxy b -> Proxy e1 -> HList l -> HList l'
instance HOccurrence' True e1 (e ': l) (e ': l) where
hOccurrence' _ _ = id
instance HOccurrence e1 l l' => HOccurrence' False e1 (e ': l) l' where
hOccurrence' _ e (HCons _ l) = hOccurrence e l
class HOccursMany e (l :: [*]) where
hOccursMany :: HList l -> [e]
instance (HOccurrence e l l', HOccursMany' e l')
=> HOccursMany e l
where
hOccursMany l = hOccursMany' (hOccurrence (Proxy::Proxy e) l)
class HOccursMany' e l where
hOccursMany' :: HList l -> [e]
instance HOccursMany' e '[] where
hOccursMany' _ = []
instance (e ~ e1, HOccursMany e l) => HOccursMany' e (e1 ': l) where
hOccursMany' (HCons e l) = e : hOccursMany l
hOccursMany1 :: forall e l l'.
(HOccurrence e l (e ': l'), HOccursMany e l') =>
HList l -> (e,[e])
hOccursMany1 l = case hOccurrence (Proxy :: Proxy e) l of
(HCons e l') -> (e,hOccursMany (l'::HList l'))
hOccursFst :: forall e l l'. HOccurrence e l (e ': l') => HList l -> e
hOccursFst l = case hOccurrence (Proxy::Proxy e) l of HCons e _ -> e
data TypeNotFound e
instance (HOccurrence e (x ': y) l', HOccurs' e l')
=> HOccurs e (HList (x ': y)) where
hOccurs = hOccurs' . hOccurrence (Proxy ::Proxy e)
class HOccurs' e l where
hOccurs' :: HList l -> e
instance Fail (TypeNotFound e) => HOccurs' e '[] where
hOccurs' = error "Data.HList.FakePrelude.Fail must have no instances"
instance (e ~ e1, HOccursNot e l) => HOccurs' e (e ': l) where
hOccurs' (HCons e _) = e
hOccursRest tip = case hOccurs tip of
x -> (x, hDeleteAtLabel (asLabel x) tip)
where asLabel :: x -> Label x
asLabel _ = Label
hOccursOpt :: forall e l l'.
(HOccurrence e l l', HOccursOpt' e l') => HList l -> Maybe e
hOccursOpt = hOccursOpt' . hOccurrence (Proxy :: Proxy e)
class HOccursOpt' e l where
hOccursOpt' :: HList l -> Maybe e
instance HOccursOpt' e '[] where
hOccursOpt' _ = Nothing
instance e ~ e1 => HOccursOpt' e (e1 ': l) where
hOccursOpt' (HCons e _) = Just e
data TypeFound e
instance HOccursNot e ('[]::[*])
instance (HEq e e1 b, HOccursNot' b e l) => HOccursNot e (e1 ': l)
class HOccursNot' (b :: Bool) e (l :: [*])
instance Fail (TypeFound e) => HOccursNot' True e l
instance HOccursNot e l => HOccursNot' False e l
instance HProject (HList l) (HList '[]) where
hProject _ = HNil
instance (HOccurs e l, HProject l (HList l'))
=> HProject l (HList (e ': l'))
where
hProject l = HCons (hOccurs l) (hProject l)