Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data VariantF (xs :: [(Type -> Type) -> Type]) (f :: Type -> Type) where
- pattern In1 :: x1 f -> VariantF (x1 ': xs) f
- pattern In2 :: x2 f -> VariantF (x1 ': (x2 ': xs)) f
- pattern In3 :: x3 f -> VariantF (x1 ': (x2 ': (x3 ': xs))) f
- pattern In4 :: x4 f -> VariantF (x1 ': (x2 ': (x3 ': (x4 ': xs)))) f
- pattern In5 :: x5 f -> VariantF (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': xs))))) f
- type family FoldSignatureF (xs :: [(Type -> Type) -> Type]) r f where ...
- class FromVariantF xs result f where
- fromVariantF :: VariantF xs f -> FoldSignatureF xs result f
- class IgnoreF (args :: [(Type -> Type) -> Type]) result f where
- ignoreF :: result -> FoldSignatureF args result f
- class InjectPosF (n :: Nat) (x :: (Type -> Type) -> Type) (xs :: [(Type -> Type) -> Type]) | n xs -> x where
- injectPosF :: SNat n -> x f -> VariantF xs f
Documentation
data VariantF (xs :: [(Type -> Type) -> Type]) (f :: Type -> Type) where Source #
A Variant is similar to nested Either
s. For example, Variant '[Int,
Bool, Char]
is isomorphic to Either Int (Either Bool Char)
. VariantF
is a variant for higher-kinded types, which means that the type-level list
holds types of kind (Type -> Type) -> Type
, and the second parameter is
the type constructor f :: Type -> Type
. To pattern match on a variant,
HereF
and ThereF
can be used:
getFromVariant :: Variant '[Int, Bool, String] -> Bool getFromVariant (ThereF (HereF b)) = b
Instances
(TraversableB x, TraversableB (VariantF xs)) => TraversableB (VariantF (x ': xs) :: (Type -> Type) -> Type) Source # | |
Defined in Options.Harg.Het.Variant btraverse :: Applicative t => (forall (a :: k). f a -> t (g a)) -> VariantF (x ': xs) f -> t (VariantF (x ': xs) g) # | |
TraversableB (VariantF ([] :: [(Type -> Type) -> Type])) Source # | |
Defined in Options.Harg.Het.Variant btraverse :: Applicative t => (forall (a :: k). f a -> t (g a)) -> VariantF [] f -> t (VariantF [] g) # | |
(FunctorB x, FunctorB (VariantF xs)) => FunctorB (VariantF (x ': xs) :: (Type -> Type) -> Type) Source # | |
Defined in Options.Harg.Het.Variant | |
FunctorB (VariantF ([] :: [(Type -> Type) -> Type])) Source # | |
Defined in Options.Harg.Het.Variant |
Helpers for pattern-matching on variants
type family FoldSignatureF (xs :: [(Type -> Type) -> Type]) r f where ... Source #
Create the signature needed for FromVariantF
to work. This constructs a
function that takes as arguments functions that can act upon each item in
the list that the VariantF
holds. For example, VariantF [a, b, c]
f
will result to the signature:
VariantF [a, b, c] f -> (a f -> r) -> (b f -> r) -> (c f -> r) -> r
FoldSignatureF (x ': xs) r f = (x f -> r) -> FoldSignatureF xs r f | |
FoldSignatureF '[] r f = r |
class FromVariantF xs result f where Source #
fromVariantF :: VariantF xs f -> FoldSignatureF xs result f Source #
Instances
(tail ~ (x' ': xs), FromVariantF tail result f, IgnoreF tail result f) => FromVariantF (x ': (x' ': xs)) result f Source # | |
Defined in Options.Harg.Het.Variant fromVariantF :: VariantF (x ': (x' ': xs)) f -> FoldSignatureF (x ': (x' ': xs)) result f Source # | |
FromVariantF (x ': ([] :: [(Type -> Type) -> Type])) result f Source # | |
Defined in Options.Harg.Het.Variant fromVariantF :: VariantF (x ': []) f -> FoldSignatureF (x ': []) result f Source # |
class IgnoreF (args :: [(Type -> Type) -> Type]) result f where Source #
ignoreF :: result -> FoldSignatureF args result f Source #
Instances
IgnoreF ([] :: [(Type -> Type) -> Type]) result f Source # | |
Defined in Options.Harg.Het.Variant ignoreF :: result -> FoldSignatureF [] result f Source # | |
IgnoreF xs result f => IgnoreF (x ': xs) result f Source # | |
Defined in Options.Harg.Het.Variant ignoreF :: result -> FoldSignatureF (x ': xs) result f Source # |
class InjectPosF (n :: Nat) (x :: (Type -> Type) -> Type) (xs :: [(Type -> Type) -> Type]) | n xs -> x where Source #
Given a type-level natural that designates a position of injection into
a VariantF
, return a function that performs this injection. For example,
S Z
which corresponds to 1 or the second position in the type-level list
the variant holds, can give the injection b f -> VariantF [a, b, c] f
.
The injection can as well be constructed without providing the position, but
it helps in case x
is not unique in xs
.
injectPosF :: SNat n -> x f -> VariantF xs f Source #
Instances
InjectPosF Z x (x ': xs) Source # | |
Defined in Options.Harg.Het.Variant | |
InjectPosF n x xs => InjectPosF (S n) x (y ': xs) Source # | |
Defined in Options.Harg.Het.Variant |