htree-0.1.1.0: An implemementation of a heterogeneous rosetree
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.HTree.List

Description

implements a heterogeneous list to use for forests of heterogeneous trees

Synopsis

heterogeneous list

data HList f ts where Source #

A heterogeneous list

>>> "bla" `HCons` 23 `HCons` HNil :: HList Identity '[ String, Int ]
HCons (Identity "bla") (HCons (Identity 23) HNil)

Constructors

HCons :: forall f x xs. f x -> HList f xs -> HList f (x : xs) infixr 5 
HNil :: forall f. HList f '[] 

Bundled Patterns

pattern (:::) :: forall f x xs. f x -> HList f xs -> HList f (x : xs) infixr 5

pattern synonym for HCons

>>> t = "bla" ::: 23 ::: HNil :: HList Identity '[ String, Int ]
>>> t
HCons (Identity "bla") (HCons (Identity 23) HNil)
>>> case t of (x ::: _) -> runIdentity x
"bla"
pattern HSing :: forall f a. f a -> HList f '[a]

pattern that allows to construct a singleton HList

>>> HSing 42 :: HList Identity '[ Int ]
HCons (Identity 42) HNil

Instances

Instances details
(forall x. Eq x => Eq (f x), Typeable f) => Eq (EList (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: EList (Has (Both Typeable Eq) f) -> EList (Has (Both Typeable Eq) f) -> Bool #

(/=) :: EList (Has (Both Typeable Eq) f) -> EList (Has (Both Typeable Eq) f) -> Bool #

Eq (f k2) => Eq (EList (HasIs k2 f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: EList (HasIs k2 f) -> EList (HasIs k2 f) -> Bool #

(/=) :: EList (HasIs k2 f) -> EList (HasIs k2 f) -> Bool #

(Show (f x), Show (HList f xs)) => Show (HList f (x ': xs)) Source # 
Instance details

Defined in Data.HTree.List

Methods

showsPrec :: Int -> HList f (x ': xs) -> ShowS #

show :: HList f (x ': xs) -> String #

showList :: [HList f (x ': xs)] -> ShowS #

Show (HList f ('[] :: [k])) Source # 
Instance details

Defined in Data.HTree.List

Methods

showsPrec :: Int -> HList f '[] -> ShowS #

show :: HList f '[] -> String #

showList :: [HList f '[]] -> ShowS #

(Eq (f x), Eq (HList f xs)) => Eq (HList f (x ': xs)) Source # 
Instance details

Defined in Data.HTree.List

Methods

(==) :: HList f (x ': xs) -> HList f (x ': xs) -> Bool #

(/=) :: HList f (x ': xs) -> HList f (x ': xs) -> Bool #

Eq (HList f ('[] :: [k])) Source # 
Instance details

Defined in Data.HTree.List

Methods

(==) :: HList f '[] -> HList f '[] -> Bool #

(/=) :: HList f '[] -> HList f '[] -> Bool #

mapping

hcmap :: forall c f g xs. All c xs => (forall a. c a => f a -> g a) -> HList f xs -> HList g xs Source #

map with a constraint that holds for all elements of the list

>>> import Data.Functor.Const
>>> hcmap @Show (Const . show . runIdentity) (42 `HCons` HSing "bla" :: HList Identity '[ Int, String ])
HCons (Const "42") (HCons (Const "\"bla\"") HNil)

hmap :: forall f g xs. (forall a. f a -> g a) -> HList f xs -> HList g xs Source #

map with a function that maps forall f a

traversing

htraverse :: forall t f g xs. Applicative t => (forall a. f a -> t (g a)) -> HList f xs -> t (HList g xs) Source #

traverse a structure with a function

hctraverse :: forall c t f g xs. (All c xs, Applicative t) => (forall a. c a => f a -> t (g a)) -> HList f xs -> t (HList g xs) Source #

traverse a structure such that a constraint holds; this is the workhorse of mapping and traversing

>>> import Data.Functor.Const
>>> hctraverse @Show (Just . Const . show . runIdentity) (42 `HCons` HSing "bla" :: HList Identity '[ Int, String ])
Just (HCons (Const "42") (HCons (Const "\"bla\"") HNil))

folding

hcFold :: forall c f b xs. All c xs => (forall a. c a => f a -> b -> b) -> b -> HList f xs -> b Source #

foldr for HLists.

helpers

allTopHList :: forall f xs. HList f xs -> Dict (All Top xs) Source #

witnesses that for all HLists, we can always derive the All Top constraint

hconcat :: forall f xs ys. HList f xs -> HList f ys -> HList f (xs ++ ys) infixr 5 Source #

concats two heterogeneous lists