Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides tools for working with unary functor combinators that represent interpretable schemas.
These are types t
that take a functor f
and return a new functor t
f
, enhancing f
with new structure and abilities.
For these, we have:
inject
:: f a -> t f a
which lets you "lift" an f a
into its transformed version, and also:
interpret
:: C t g
=> (forall x. f a -> g a)
-> t f a
-> g a
that lets you "interpret" a t f a
into a context g a
, essentially
"running" the computaiton that it encodes. The context is required to
have a typeclass constraints that reflects what is "required" to be able
to run a functor combinator.
Every single instance provides different tools. Check out the instance list for a nice list of useful combinators, or also the README for a high-level rundown.
See Data.Functor.Tensor for binary functor combinators that mix together two or more different functors.
Documentation
class Inject t => Interpret t where Source #
An Interpret
lets us move in and out of the "enhanced" Functor
.
For example,
is Free
ff
enhanced with monadic structure. We get:
inject
:: f a ->Free
f ainterpret
::Monad
m => (forall x. f x -> m x) ->Free
f a -> m a
inject
will let us use our f
inside the enhanced
.
Free
finterpret
will let us "extract" the f
from a
if
we can give an interpreting function that interprets Free
ff
into some
target Monad
.
The type family C
tells us the typeclass constraint of the "target"
functor. For Free
, it is Monad
, but for other Interpret
instances, we might have other constraints.
We enforce that:
interpret
id .inject
== id -- orretract
.inject
== id
That is, if we lift a value into our structure, then immediately interpret it out as itself, it should lave the value unchanged.
retract :: C t f => t f ~> f Source #
Remove the f
out of the enhanced t f
structure, provided that
f
satisfies the necessary constraints. If it doesn't, it needs to
be properly interpret
ed out.
interpret :: C t g => (f ~> g) -> t f ~> g Source #
Given an "interpeting function" from f
to g
, interpret the f
out of the t f
into a final context g
.
Instances
Interpret Ap Source # | A free |
Interpret Ap Source # | A free |
Interpret Ap Source # | A free |
Interpret Alt Source # | A free |
Interpret Coyoneda Source # | A free |
Interpret WrappedApplicative Source # | |
Defined in Data.HFunctor.Interpret type C WrappedApplicative :: (Type -> Type) -> Constraint Source # retract :: C WrappedApplicative f => WrappedApplicative f ~> f Source # interpret :: C WrappedApplicative g => (f ~> g) -> WrappedApplicative f ~> g Source # | |
Interpret MaybeApply Source # | A free |
Defined in Data.HFunctor.Interpret type C MaybeApply :: (Type -> Type) -> Constraint Source # retract :: C MaybeApply f => MaybeApply f ~> f Source # interpret :: C MaybeApply g => (f ~> g) -> MaybeApply f ~> g Source # | |
Interpret Lift Source # | A free |
Interpret ListF Source # | A free |
Interpret NonEmptyF Source # | A free |
Interpret MaybeF Source # | Technically, |
Interpret Free1 Source # | A free |
Interpret Free Source # | A free |
Interpret Ap1 Source # | |
Monoid e => Interpret (EnvT e) Source # | |
Interpret (IdentityT :: (Type -> Type) -> Type -> Type) Source # | A free |
Interpret (These1 f) Source # | Technically, |
Interpret (Reverse :: (Type -> Type) -> Type -> Type) Source # | |
Interpret (Backwards :: (Type -> Type) -> Type -> Type) Source # | |
Monoid k => Interpret (MapF k) Source # | |
Monoid k => Interpret (NEMapF k) Source # | |
Interpret (Step :: (Type -> Type) -> Type -> Type) Source # | |
Interpret (Steps :: (Type -> Type) -> Type -> Type) Source # | |
Interpret (Flagged :: (Type -> Type) -> Type -> Type) Source # | |
Interpret (Final c) Source # | |
Interpret ((:+:) f) Source # | Technically, |
Plus f => Interpret ((:*:) f) Source # | |
Plus f => Interpret (Product f) Source # | |
Interpret (Sum f) Source # | Technically, |
(Interpret s, Interpret t) => Interpret (ComposeT s t) Source # | |
Interpret (ReaderT r :: (Type -> Type) -> Type -> Type) Source # | A free |
Interpret (ProxyF :: (Type -> Type) -> Type -> Type) Source # | The only way for this to obey |
Interpret t => Interpret (HFree t) Source # | Never uses |
Interpret t => Interpret (HLift t) Source # | Never uses |
(HBifunctor t, Semigroupoidal t) => Interpret (Chain1 t) Source # | |
Interpret (M1 i c :: (Type -> Type) -> Type -> Type) Source # | |
Monoid e => Interpret (ConstF e :: (Type -> Type) -> Type -> Type) Source # | The only way for this to obey |
Interpret (RightF f :: (Type -> Type) -> Type -> Type) Source # | |
(Monoidal t, i ~ I t) => Interpret (Chain t i) Source # | We can collapse and interpret an |
forI :: (Interpret t, C t g) => t f a -> (f ~> g) -> g a Source #
A convenient flipped version of interpret
.
Utilities
getI :: (Interpret t, C t (Const b)) => (forall x. f x -> b) -> t f a -> b Source #
Useful wrapper over interpret
to allow you to directly extract
a value b
out of the t f a
, if you can convert f x
into b
.
Note that depending on the constraints on the interpretation of t
, you
may have extra constraints on b
.
- If
isC
tUnconstrained
, there are no constraints onb
- If
isC
tApply
,b
needs to be an instance ofSemigroup
- If
isC
tApplicative
,b
needs to be an instance ofMonoid
For some constraints (like Monad
), this will not be usable.
-- get the length of theMap String
in theStep
.collectI
length :: Step (Map String) Bool -> Int
collectI :: (Interpret t, C t (Const [b])) => (forall x. f x -> b) -> t f a -> [b] Source #
Useful wrapper over getI
to allow you to collect a b
from all
instances of f
inside a t f a
.
This will work if
is C
tUnconstrained
, Apply
, or Applicative
.
-- get the lengths of allMap String
s in theAp
.collectI
length :: Ap (Map String) Bool -> [Int]
class (c a, d a) => AndC c d a Source #
A constraint on a
for both c a
and d a
. Requiring
is the same as requiring AndC
Show
Eq
a(
.Show
a, Eq
a)
Instances
(c a, d a) => AndC (c :: k -> Constraint) (d :: k -> Constraint) (a :: k) Source # | |
Defined in Data.HFunctor.Interpret |