Copyright | Copyright (c) Jordan Woehr 2018 |
---|---|
License | BSD |
Maintainer | Jordan Woehr |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module defines the VarF
type and related functions and instances.
This type wraps a variant of types that have all had the same type applied
to them. Most often this will be a variant constructed with a row of
functors.
Synopsis
- type family ApplyRow (x :: *) (r :: Row (* -> *)) :: Row * where ...
- type family ApplyLT (x :: *) (r :: [LT (* -> *)]) :: [LT *] where ...
- newtype VarF (r :: Row (* -> *)) x = VarF {}
- newtype VarF' x (r :: Row (* -> *)) = VarF' {}
- newtype FlipApp (a :: *) (f :: * -> *) = FlipApp (f a)
- mapVarF :: (Var (ApplyRow x u) -> Var (ApplyRow x v)) -> VarF u x -> VarF v x
- varFAlg :: forall (c :: (* -> *) -> Constraint) (r :: Row (* -> *)) (x :: *) (y :: *). Forall r c => (forall f. c f => f x -> y) -> VarF r x -> y
- varFAlg' :: forall (r :: Row (* -> *)) (x :: *) (y :: *). Forall r Unconstrained1 => (forall f. Unconstrained1 f => f x -> y) -> VarF r x -> y
- type family RowFromTo (a :: Row *) (b :: *) :: Row * where ...
- type family RowFromToR (a :: [LT *]) (b :: *) :: [LT *] where ...
- reduceVarF :: forall r s t x r' s' t'. (t ≈ (r .\\ s), r' ~ ApplyRow x r, s' ~ ApplyRow x s, s' ≈ (r' .\\ t'), t' ≈ (r' .\\ s'), Disjoint s' t', Switch t' (RowFromTo t' (VarF s x)) (VarF s x)) => Rec (RowFromTo t' (VarF s x)) -> VarF r x -> VarF s x
- type OpenAlg r l f v = ((ApplyRow v r .! l) ≈ f v, AllUniqueLabels (ApplyRow v r))
Documentation
type family ApplyLT (x :: *) (r :: [LT (* -> *)]) :: [LT *] where ... Source #
Apply a type to each element of an LT
.
newtype VarF (r :: Row (* -> *)) x Source #
A newtype that wraps a variant. The variant is a row made up of
(* -> *) that all have the type x applied to them with ApplyRow
.
newtype VarF' x (r :: Row (* -> *)) Source #
A helper for writing functions with metamorph'
. This type reverses the
argument order of VarF
so the Row
parameter is last.
newtype FlipApp (a :: *) (f :: * -> *) Source #
A helper for writing functions with metamorph'
. This type wraps an
f a but takes the type arguments in the order a f.
FlipApp (f a) |
mapVarF :: (Var (ApplyRow x u) -> Var (ApplyRow x v)) -> VarF u x -> VarF v x Source #
Apply a function to the variant within a VarF
.
Since: 1.0.0
varFAlg :: forall (c :: (* -> *) -> Constraint) (r :: Row (* -> *)) (x :: *) (y :: *). Forall r c => (forall f. c f => f x -> y) -> VarF r x -> y Source #
This function is useful for implementing functions that are used as
catamorphisms, and sometimes VarF
instances. The function applies its
first argument to whatever variant is wrapped by VarF r x provided all
elements of the row r are constrained by c.
For an example, see the Show1
instance implementation.
Since: 1.0.0
varFAlg' :: forall (r :: Row (* -> *)) (x :: *) (y :: *). Forall r Unconstrained1 => (forall f. Unconstrained1 f => f x -> y) -> VarF r x -> y Source #
The same as varFAlg
, but with the constraint fixed to Unconstrained1
.
Since: 1.0.0
type family RowFromTo (a :: Row *) (b :: *) :: Row * where ... Source #
RowFromTo fs b := for (l,a) in fs; SUM [ l :-> (a -> b) ]
RowFromTo (R r) b = R (RowFromToR r b) |
type family RowFromToR (a :: [LT *]) (b :: *) :: [LT *] where ... Source #
RowFromToR '[] x = '[] | |
RowFromToR ((l :-> a) ': rs) b = (l :-> (a -> b)) ': RowFromToR rs b |
reduceVarF :: forall r s t x r' s' t'. (t ≈ (r .\\ s), r' ~ ApplyRow x r, s' ~ ApplyRow x s, s' ≈ (r' .\\ t'), t' ≈ (r' .\\ s'), Disjoint s' t', Switch t' (RowFromTo t' (VarF s x)) (VarF s x)) => Rec (RowFromTo t' (VarF s x)) -> VarF r x -> VarF s x Source #
Given a record of functions, use those functions to remove the corresponding rows from the input. Type errors will ensue if the record contains fields of the output variant.
Since: 1.0.0
type OpenAlg r l f v = ((ApplyRow v r .! l) ≈ f v, AllUniqueLabels (ApplyRow v r)) Source #
A type constraint synonym for convenience that can be used in, for example, patterns. The variables r (representing a Row) and v (representing the type applied to f) are generally left abstract. The variable l is the label corresponding to f v.
The order of variables are in the same order as the equality constraint in the synonym, making it easy to remember.
Since: 1.0.0