| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Data.HTree.List
Description
implements a heterogeneous list to use for forests of heterogeneous trees
Synopsis
- data HList f ts where
 - hcmap :: forall c f g xs. All c xs => (forall a. c a => f a -> g a) -> HList f xs -> HList g xs
 - hmap :: forall f g xs. (forall a. f a -> g a) -> HList f xs -> HList g xs
 - htraverse :: forall t f g xs. Applicative t => (forall a. f a -> t (g a)) -> HList f xs -> t (HList g xs)
 - 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)
 - hcFold :: forall c f b xs. All c xs => (forall a. c a => f a -> b -> b) -> b -> HList f xs -> b
 - allTopHList :: forall f xs. HList f xs -> Dict (All Top xs)
 - hconcat :: forall f xs ys. HList f xs -> HList f ys -> HList f (xs ++ ys)
 
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  
  | 
| pattern HSing :: forall f a. f a -> HList f '[a] | pattern that allows to construct a singleton HList 
  | 
Instances
| (forall x. Eq x => Eq (f x), Typeable f) => Eq (EList (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # | |
| Eq (f k2) => Eq (EList (HasIs k2 f)) Source # | |
| (Show (f x), Show (HList f xs)) => Show (HList f (x ': xs)) Source # | |
| Show (HList f ('[] :: [k])) Source # | |
| (Eq (f x), Eq (HList f xs)) => Eq (HList f (x ': xs)) Source # | |
| Eq (HList f ('[] :: [k])) Source # | |
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.