Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => Carrier m where
- type Algebra r m = forall x. Union r m x -> m x
- type Algebra' r m a = Union r m a -> m a
- type Reformulation r p m = forall z. Monad z => (forall x. m x -> z x) -> Algebra p z -> Algebra r z
- type Reformulation' r p m z a = (forall x. m x -> z x) -> Algebra p z -> Algebra' r z a
- powerAlg :: forall e r m a. RepresentationalEff e => Algebra' r m a -> (e m a -> m a) -> Algebra' (e ': r) m a
- powerAlg' :: forall e r m a. Algebra' r m a -> (forall z. Coercible z m => e z a -> m a) -> Algebra' (e ': r) m a
- weakenAlg :: Algebra' (e ': r) m a -> Algebra' r m a
- coerceAlg :: forall n m e a b. (Coercible n m, RepresentationalEff e) => (e m a -> m b) -> e n a -> n b
- liftReform :: (MonadTrans t, Monad m) => Reformulation' r p m z a -> Reformulation' r p (t m) z a
- addDeriv :: (RepresentationalEff e, Monad m) => (forall z x. (Carrier z, Derivs z ~ r, Prims z ~ p, MonadBase m z) => e (Effly z) x -> Effly z x) -> Reformulation r p m -> Reformulation (e ': r) p m
- addPrim :: forall e r p m z a. Monad z => Reformulation' r p m z a -> Reformulation' (e ': r) (e ': p) m z a
- weakenReform :: Reformulation' (e ': r) p m z a -> Reformulation' r p m z a
- weakenReformUnder1 :: forall e' e r p m z a. Reformulation' (e ': (e' ': r)) p m z a -> Reformulation' (e ': r) p m z a
- weakenReformUnder :: forall new e r p m z a. KnownList new => Reformulation' (e ': Append new r) p m z a -> Reformulation' (e ': r) p m z a
- weakenReformUnderMany :: forall top new r p m z a. (KnownList top, KnownList new) => Reformulation' (Append top (Append new r)) p m z a -> Reformulation' (Append top r) p m z a
- coerceReform :: Coercible m n => Reformulation' r p m z a -> Reformulation' r p n z a
- type family StripPrefix xs r where ...
- module Data.Coerce
- module Control.Effect.Internal.Derive
- module Control.Effect.Primitive
- module Control.Effect.Union
Core types
class Monad m => Carrier m where Source #
The class of effect carriers, and the underlying mechanism with which effects are implemented.
Each carrier is able to implement a number of derived effects, and primitive effects. Users usually only interact with derived effects, as these determine the effects that users have access to.
The standard interpretation tools are typically powerful enough to
let you avoid making instances of this class directly. If you need to make
your own instance of Carrier
, import Control.Effect.Carrier and consult the
wiki.
type Derivs m :: [Effect] Source #
The derived effects that m
carries. Each derived effect is eventually
reformulated into terms of the primitive effects
or other
effects in Prims
m
.Derivs
m
In application code, you gain access to effects by placing membership
constraints upon
. You can use Derivs
mEff
or Effs
for this
purpose.
Although rarely relevant for users,
can also contain effects
that aren't expressed in terms of other effects, as longs as the handlers
for those effects can be lifted generically using Derivs
mlift
. Such effects don't
need to be part of
, which is exclusively for primitive effects
whose handlers need special treatment to be lifted.Prims
m
For example, first order effects such as State
never need to be part of
. Certain higher-order effects -
such as Prims
mCont
- can also be handled such that they
never need to be primitive.
type Prims m :: [Effect] Source #
The primitive effects that m
carries. These are higher-order effects
whose handlers aren't expressed in terms of other effects, and thus need to
be lifted on a carrier-by-carrier basis.
Never place membership constraints on
.
You should only gain access to effects by placing membership constraints
on Prims
m
.Derivs
m
However, running interpreters may place other kinds of constraints upon
, namely threading constraints, marked by the use of
Prims
mThreaders
.
If you want to run such an effect interpreter inside application code, you
have to propagate such threading constraints through your application.
should only contain higher-order effects that can't be lifted
generically using Prims
mlift
. Any other effects can be placed in
.Derivs
m
algPrims :: Algebra' (Prims m) m a Source #
An m
-based Algebra
(i.e effect handler) over the union
of the primitive effects:
effects that aren't formulated in terms of other effects.
See Prims
.
reformulate :: Monad z => Reformulation' (Derivs m) (Prims m) m z a Source #
Any Carrier
m
must provide a way to describe the derived effects it
carries in terms of the primitive effects.
reformulate
is that decription: given any monad z
such that
z
lifts m
, then a z
-based Algebra
(i.e. effect handler)
over the derived effects can be created out of a z
-based Algebra
over
the primitive effects.
algDerivs :: Algebra' (Derivs m) m a Source #
An m
-based algebra (i.e. effect handler) over the union of derived
effects (see
).Derivs
m
This is what send
makes use of.
algDerivs
is subject to the law:
algDerivs =reformulate
idalgPrims
which serves as the default implementation.
Instances
type Algebra r m = forall x. Union r m x -> m x Source #
An
desribes a collection of effect handlers for Algebra
r mm
over
all effects in the list r
.
type Algebra' r m a = Union r m a -> m a Source #
A first-rank type which can often be used instead of Algebra
type Reformulation r p m = forall z. Monad z => (forall x. m x -> z x) -> Algebra p z -> Algebra r z Source #
The type of reformulate
.
A
describes how the derived effects Reformulation
r p mr
are
formulated in terms of the primitive effects p
and first-order operations
of m
.
This is done by providing an
for any monad Algebra
r zz
that lifts
m
and implements an Algebra
over p
.
type Reformulation' r p m z a = (forall x. m x -> z x) -> Algebra p z -> Algebra' r z a Source #
A less higher-rank variant of Reformulation
, which is sometimes
important.
Combinators for Algebra
s
powerAlg :: forall e r m a. RepresentationalEff e => Algebra' r m a -> (e m a -> m a) -> Algebra' (e ': r) m a Source #
Strengthen an Algebra
by providing a handler for a new effect e
.
powerAlg' :: forall e r m a. Algebra' r m a -> (forall z. Coercible z m => e z a -> m a) -> Algebra' (e ': r) m a Source #
weakenAlg :: Algebra' (e ': r) m a -> Algebra' r m a Source #
Weaken an Algebra
by removing the topmost effect.
coerceAlg :: forall n m e a b. (Coercible n m, RepresentationalEff e) => (e m a -> m b) -> e n a -> n b Source #
Combinators for Reformulation
s
liftReform :: (MonadTrans t, Monad m) => Reformulation' r p m z a -> Reformulation' r p (t m) z a Source #
Lift an m
-based Reformulation
to a t m
-based Reformulation
,
where t
is any MonadTrans
addDeriv :: (RepresentationalEff e, Monad m) => (forall z x. (Carrier z, Derivs z ~ r, Prims z ~ p, MonadBase m z) => e (Effly z) x -> Effly z x) -> Reformulation r p m -> Reformulation (e ': r) p m Source #
Add a derived effect to a Reformulation
by providing a handler for that effect.
The handler is an EffHandler
, but with derived and primitive effects
determined by the transformed Reformulation
.
addPrim :: forall e r p m z a. Monad z => Reformulation' r p m z a -> Reformulation' (e ': r) (e ': p) m z a Source #
Add a primitive effect and corresponding derived effect to a Reformulation
.
weakenReform :: Reformulation' (e ': r) p m z a -> Reformulation' r p m z a Source #
Weaken a Reformulation
by removing the topmost
derived effect.
weakenReformUnder1 :: forall e' e r p m z a. Reformulation' (e ': (e' ': r)) p m z a -> Reformulation' (e ': r) p m z a Source #
Weaken a Reformulation
by removing a derived effect under
the topmost effect.
weakenReformUnder :: forall new e r p m z a. KnownList new => Reformulation' (e ': Append new r) p m z a -> Reformulation' (e ': r) p m z a Source #
Weaken a Reformulation
by removing a number of derived effects under
the topmost effect.
This needs a type application to specify what effects to remove.
weakenReformUnderMany :: forall top new r p m z a. (KnownList top, KnownList new) => Reformulation' (Append top (Append new r)) p m z a -> Reformulation' (Append top r) p m z a Source #
Weaken a Reformulation
by removing a number of derived effects under
a number of topmost effects.
This needs a type application to specify the top effects of the stack underneath which effects are removed, and another type application to specify what effects to remove.
For example:
weakenReformUnderMany @'[Catch
e] @'[Optional
((->) e)] :: Reformulation (Catch
e ':Optional
((->) e) ': r) p m -> Reformulation (Catch
e ': r) p m
coerceReform :: Coercible m n => Reformulation' r p m z a -> Reformulation' r p n z a Source #
Hiding effects
type family StripPrefix xs r where ... Source #
Remove the prefix xs
from the list r
.
IntroC
, ReinterpretC
and friends don't
as much introduce effects as they hide them, through removing effects from
the derived effects that the transformed carrier carries.
This is done thorugh StripPrefix
.
For example:
Derivs
(ReinterpretSimpleC
e '[newE, newE2]) = e ':StripPrefix
'[newE, newE2] (Derivs
m)
StripPrefix '[] r = r | |
StripPrefix (x ': xs) (x ': r) = StripPrefix xs r |
Type Coercion
module Data.Coerce
Common classes for newtype deriving
Primitive effects
module Control.Effect.Primitive
Union
module Control.Effect.Union