Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data AssocListF (ts :: [Symbol]) (xs :: [(Type -> Type) -> Type]) (f :: Type -> Type) where
- ANil :: AssocListF '[] '[] f
- ACons :: x f -> AssocListF ts xs f -> AssocListF (t ': ts) (x ': xs) f
- type family l :+ r = (res :: (Type -> Type) -> Type) where ...
- pattern (:+) :: x f -> AssocListF ts xs f -> AssocListF (t ': ts) (x ': xs) f
- data (t :: Symbol) :-> (v :: (Type -> Type) -> Type) :: (Type -> Type) -> Type
- class MapAssocList (as :: [(Type -> Type) -> Type]) where
- mapAssocList :: (forall a. FunctorB a => a f -> a g) -> AssocListF ts as f -> AssocListF ts as g
Documentation
data AssocListF (ts :: [Symbol]) (xs :: [(Type -> Type) -> Type]) (f :: Type -> Type) where Source #
A heterogeneous list that holds higher-kinded types and the associated
type constructor, along with a type level list of Symbol
s that act
as tags for each type.
ANil :: AssocListF '[] '[] f | |
ACons :: x f -> AssocListF ts xs f -> AssocListF (t ': ts) (x ': xs) f |
type family l :+ r = (res :: (Type -> Type) -> Type) where ... infixr 4 Source #
Helper type-level function to construct an AssocList
which is not
yet applied to the type constructor that needs to be fully applied.
type Config = "run" :-> RunConfig :+ "test" :-> TestConfig
Config
above has type (Type -> Type) -> Type
, and requires a type
like Opt
to be fully applied.
(tl :-> vl) :+ (tr :-> vr) = AssocListF '[tl, tr] '[vl, vr] | |
(tl :-> vl) :+ (AssocListF ts vs) = AssocListF (tl ': ts) (vl ': vs) | |
l :+ r = TypeError (((Text "Invalid type for tagged options. Construct like this:" :$$: Text "type MyConfig") :$$: Text " = \"one\" :-> ConfigForOne") :$$: Text " :+ \"two\" :-> ConfigForTwo") |
pattern (:+) :: x f -> AssocListF ts xs f -> AssocListF (t ': ts) (x ': xs) f infixr 4 Source #
class MapAssocList (as :: [(Type -> Type) -> Type]) where Source #
mapAssocList :: (forall a. FunctorB a => a f -> a g) -> AssocListF ts as f -> AssocListF ts as g Source #
Apply a function to all higher-kinded types in an AssocList
.
Instances
MapAssocList ([] :: [(Type -> Type) -> Type]) Source # | |
Defined in Options.Harg.Het.HList mapAssocList :: (forall (a :: (Type -> Type) -> Type). FunctorB a => a f -> a g) -> AssocListF ts [] f -> AssocListF ts [] g Source # | |
(MapAssocList as, FunctorB a) => MapAssocList (a ': as) Source # | |
Defined in Options.Harg.Het.HList mapAssocList :: (forall (a0 :: (Type -> Type) -> Type). FunctorB a0 => a0 f -> a0 g) -> AssocListF ts (a ': as) f -> AssocListF ts (a ': as) g Source # |