-
Notifications
You must be signed in to change notification settings - Fork 7
Advanced Topics
- The Various Ways To Interpret Effects
- Effect Reinterpretation
- Local and Global State Semantics
- Effect Newtypes
- Primitive Effects
- Split Interpretation
- Making effects
RepresentationalEff
- Novel Carriers
- Effect Interception
The library offers three main ways to interpret effects. For derived effects, there is interpret
, interpretSimple
, and interpretViaHandler
/Handler
.
They all serve the same purpose, so why are there three of them?
Ideally, there wouldn't be: interpret
should be all that's necessary, but the thing complicating it is that interpret
has a higher-rank type. This is because interpret
needs to make use of reflection in order to reify the provided interpreter to the constraint-level so that the carrier for interpret
may make use of it. But because of this, the carrier is enclosed within a forall
to make this reflection safe.
The reason this matters is that higher-rank types are hell for type inference, and because of that interpret
can't be used partially applied. You can't make an interpreter out of interpret
and then compose it with other interpreters using .
, &
, or anything else of that nature. Your only options are parenthesis and $
.
interpretSimple
and interpretViaHandler
serves as alternatives because of this problem.
-
interpretSimple
has a very similar signature tointerpret
, but makes use ofReaderT
to make the handler available to the carrier. This makes it possible to use partially applied, but is significantly less performant, and also incurs aReaderThreads
threading constraint. (If you're unfamiliar with threading constraints, consult the documentation forThreaders
and/or the introductory section of Primitive Effects) - With
interpretViaHandler
you provide the handler via an instance of the type classHandler
. This is as performant asinterpret
, and doesn't require a higher-ranked type -- however, since the handler is separated from the interpreter, you can't use values of the environment inside of the handler, which matters when you want your interpreter to take additional arguments. MakingHandler
instances also typically requires enablingUndecidableInstances
.
Because of the issues with interpret
and interpretSimple
, in-other-words
makes use of interpretViaHandler
for its interpreters as much as possible -- and for every interpreter where interpretViaHandler
can't be used, it provides both a regular variant that makes use of interpret
internally, and a variant that makes use of interpretSimple
internally.
For inexperienced users or for users where performance is secondary, interpretSimple
and -Simple
variants of interpretations are typically the better choices. The greatest problem interpretSimple
may pose is the ReaderThreads
threading constraint; if you want to create an interpreter to be used in application code, you should consider using interpret
or interpretViaHandler
instead.
The reason why interpret
gets to be called interpret
(instead of having interpretSimple
be called interpret
and interpret
be called, say, interpretFast
) is the hope that quick look impredicativity will solve the issues with interpret
, at which point it may become the go-to instead of interpretSimple
.
in-other-words
provides a variety of tools to introduce effects,
which may be used to interpret effects in terms of these newly-introduced effects.
The benefit of this is that the introduced effects are invisible to the rest of the program.
For example, consider the following program:
data Counter m a where
Probe :: Counter m Int
type CounterC m = InterpretSimpleC Counter (StateC Int m)
runCounter :: ( Carrier m
, Threaders '[ReaderThreads, StateThreads] m p
)
=> CounterC m a -> m a
runCounter = runState 0 . interpretSimple (\case
Probe -> state' (\s -> (s+1,s))
)
This works fine, but it has a problem: the State
effect here is only intended
to be used for runCounter
, but it's visible to the entire program:
type Derivs (CounterC m) = Counter ': State Int ': Derivs m
That means that if the application uses a State Int
effect, it's possible it could target the
runState
in runCounter
.
This could be a nasty source of bugs if there's another State Int
effect later down the line that gets interfered with because of that.
The solution is to introduce the State
effect instead. When you want to introduce
effects under one effect that you're interpreting, reinterpret
and friends work best:
data Counter m a where
Probe :: Counter m Int
type CounterC m = ReinterpretSimpleC Counter '[State Int] (StateC Int m)
runCounter :: ( Carrier m
, Threaders '[ReaderThreads, StateThreads] m p
)
=> CounterC m a -> m a
runCounter = evalState 0 . reinterpretSimple (\case
Probe -> state' (\s -> (s+1,s))
)
This version no longer exposes State Int
to the outside world, and thus can't interfere with the rest of the program:
type Derivs (CounterC m) = Counter ': Derivs m
This works because ReinterpretSimpleC
does something special: its effect stack hides the State Int
effect of StateC Int m
by
using a type family StripPrefix
:
type Derivs (CounterC m) = Derivs (ReinterpretSimpleC Counter '[State Int] (StateC Int m))
= Counter ': StripPrefix '[State Int] (Derivs (StateC Int m))
= Counter ': StripPrefix '[State Int] (State Int ': Derivs m)
= Counter ': Derivs m
If you want to introduce effects underneath multiple effects, then reinterpret
isn't powerful enough:
you need IntroC
and introUnderMany
, and combine them with interpret
. Here's an example:
type AccumLogC m =
-- v the top effects of the stack under which new effects are introduced
IntroC '[Tell String, Ask String] '[State String] (
InterpretSimpleC (Tell String) ( -- ^ the newly introduced effects
InterpretSimpleC (Ask String) (
StateC String m
)))
runAccumLog :: ( Carrier m
, Threaders '[ReaderThreads, StateThreads] m p
)
=> AccumLogC m a -> m a
runAccumLog
evalState ""
. interpretSimple (\case
Ask -> get
)
. interpretSimple (\case
Tell s -> modify' (++ s)
)
. introUnderMany
introUnderMany
introduces the State Int
effect underneath the interpreted Tell String
and Ask String
effects,
thus making that effect invisible to the rest of the program.
type Derivs (AccumLogC m) = Tell String ': Ask String ': Derivs m
There are two problems with CounterC
and AccumLogC
:
- They're made up of multiple monad transformers, so if you want to lift
m
toAccumLogC m
/CounterC m
, you need to uselift
multiple times. - Because the monad transformers are discrete, it exposes the internal implementation of the interpreters in a way users may mess around with.
For example, there's nothing stopping users from, say, creating a
StateC String m
/StateC Int m
value, lift it a couple of times, and then pass it intorunAccumLog
/runCounter
, which then won't do the right thing.
The solution to both of these problems is a monad transformer that composes monad transformer: CompositionC
.
- Since
CompositionC
composes the monad transformers, a singlelift
would liftm
past all of the monad transformers. -
Control.Effect
doesn't expose a way to construct aCompositionC
value out of a of a partial stack of the composed monad transformers, so there's no way for users to do the wrong thing (unless they import internal modules).
CompositionC
has the runComposition
interpreter to bring the composed monad transformers down to individual layers.
Here's how AccumLogC
would look like using CompositionC
:
type AccumLogC = CompositionC
'[ IntroC '[Tell String, Ask String] '[State String]
, InterpretSimpleC (Tell String)
, InterpretSimpleC (Ask String)
, StateC String
]
runAccumLog :: ( Carrier m
, Threaders '[ReaderThreads, StateThreads] m p
)
=> AccumLogC m a -> m a
runAccumLog
evalState ""
. interpretSimple (\case
Ask -> get
)
. interpretSimple (\case
Tell s -> modify' (++ s)
)
. introUnderMany
. runComposition
Note that interpreters that make use of interpret
are very difficult to compose using CompositionC
due to the higher-rank type.
It's possible, but not intuitive. Because of this, interpretSimple
and interpretViaHandler
are better choices in this case.
Here's how you would implement AccumLogC
using interpret
instead of interpretSimple
:
type AccumLogC' s s' = CompositionC
'[ IntroC '[Tell String, Ask String] '[State String]
, InterpretC (ViaReifiedH s) (Tell String)
, InterpretC (ViaReifiedH s') (Ask String)
, StateC String
]
type AccumLogC m a =
forall s s'
. ( ReifiesHandler s (Tell String)
(InterpretC (ViaReifiedH s') (Ask String)
(StateC String m)
)
, ReifiesHandler s' (Ask String)
(StateC String m)
)
=> AccumLogC' s s' m a
runAccumLog :: ( Carrier m
, Threaders '[StateThreads] m p
)
=> AccumLogC m a -> m a
runAccumLog m =
evalState ""
$ interpret (\case
Ask -> get
)
$ interpret (\case
Tell s -> modify' (++ s)
)
$ introUnderMany
$ runComposition
$ m
Pretty terrible. Only use this if you really want the usability benefits CompositionC
gives you and the performance benefits interpret
gives you (and you can't use interpretViaHandler
).
Like polysemy
, fused-effects
, and even mtl
, the order of certain interpreters could matter for how the effects they interpret interact with one another.
These are pure interpreters, interpreters that interpret an effect purely -- not in terms of other effects or the final monad. Examples include runState
and runError
, but not stateToIO
or errorToIO
.
Effects interpreted using pure interpreters are said to have local/global state semantics relative to one another depending on in what order they are interpreted. Effects which are purely interpreted have global state semantics compared to effects that have been purely interpreted before them, and local state semantics compared to all effects purely interpreted after them.
For example, for the program:
mainProgram :: Effs '[State String, Error ()] m
=> m ()
mainProgram = (put "global" >> throw ()) `catch` \() -> return ()
main :: Either () String
main = run $ runError @() $ execState "local" $ mainProgram
State String
has local state semantics relative to Error ()
, and Error ()
has global state semantics relative to State String
.
In this case, that means that exceptions thrown will revert changes to the state up until the nearest enclosing catch
. So main == Right "local"
.
If we switch the order of interpreters:
main :: String
main = run $ execState "local" $ runError @() $ mainProgram
Then State String
has global state semantics relative to Error ()
, so changes to the state won't get reverted by exceptions. main == "global"
. Similar relationships exist with other effects. For example:
- If a
Cont
effect is global relative to aTell
effect, then thetell
s executed after acallCC
get reverted if the abortive continuation provided by thecallCC
is executed. If theTell
effect is global instead, then alltell
s persist past the execution of abortive continuations. - If a
State
effect is global relative to aNonDet
effect, then modifications to the state persist between branches. If theNonDet
effect is global instead, then the modifications to the state are local to each branch. - If an
Error
effect is global relative to aNonDet
effect, then an exception thrown in a branch will abort all pending branches up to the nearest enclosingcatch
. If theNonDet
effect is global instead, then an exception will abort the branch it's thrown in only.
Note that this is only true for pure interpreters; it's not as easy to tell how effects interpreted by other kinds of interpreters interact.
- Effects interpreted in terms of the final monad are always global relative to effects interpreted purely.
- State semantics of effects interpreted in terms of other effects depend on how those other effects are interpreted.
- If two effects are both interpreted in terms of the final monad, then state semantics depend on the final monad. For example, when using
stateToIO
anderrorToIO
, theState
effect always has global state semantics relative to theError
effect.
You may want to make effects that act as newtypes of other effects. in-other-words
provides the Control.Effect.Newtype
module for that purpose. As an example of an effect newtype, Conc
is just a newtype of Unlift IO
:
newtype Conc m a = Conc (Unlift IO m a)
Conc
simply doesn't expose its constructor, so users will only gain access to the limited uses of Unlift IO
that Conc
allows through its associated actions.
You can create actions of the newtype by making use of wrapWith
:
import qualified Control.Concurrent.Async as A
async :: Eff Conc m => m a -> m (A.Async a)
async m = wrapWith Conc $ unlift $ \lower -> A.async (lower (lift m))
(lift
is necessary since wrapWith
is actually an interpreter for a carrier that gives you temporary access to the wrapped effect)
Unwrapping an effect newtype can be done in one of two ways. Either you just (re)interpret it as a regular effect and use send
:
type ConcToIOC = CompositionC
'[ ReinterpretSimpleC Conc '[Unlift IO]
, UnliftToFinalC IO
]
concToIO :: ( MonadBaseControlPure IO m
, Threaders '[ReaderThreads] m p
)
=> ConcToIOC m a
-> m a
concToIO =
unliftToFinal
. reinterpretSimple (\(Conc e) -> send e)
. runComposition
Or, if you care about performance, you can make an instance of the EffNewtype
type class, and use unwrap
/unwrapTop
.
instance EffNewtype Conc where UnwrappedEff Conc = Unlift IO
type ConcToIOC = CompositionC
'[ UnwrapTopC Conc
, UnliftToFinalC IO
]
concToIO :: MonadBaseControlPure IO m => ConcToIOC m a -> m a
concToIO =
unliftToFinal
. unwrapTop
. runComposition
You can also derive EffNewtype
via WrapperOf
:
newtype Conc m a = Conc (Unlift IO m a)
deriving EffNewtype via Conc `WrapperOf` Unlift IO
in-other-words
distinguishes between derived and primitive effects. For further reading, see The inner workings of the library.
An effect is considered derived or primitive depending on how it's interpreted (a particular effect doesn't have to be exclusively one or the other.)
The effects users usually deal with -- including effects they define for themselves -- are derived, meaning their handlers are defined in terms of other effects and/or first-order operations of the current monad. The benefit of derived effects is that their handlers can be generically lifted.
Primitive effects, on the other hand, are higher-order effects whose handlers need to make use of higher-order operations of the current monad (that don't belong to another effect). Such handlers need to operate on the current monad directly, which means that they need to be lifted on a transformer-by-transformer basis. The ability of a monad transformer to lift handlers of a primitive effect is called threading that effect, and is represented by the ThreadsEff
class.
Interpreters may emit threading constraints, which correspond to the ability of the carrier used by the interpreter to thread the
primitive effects currently in use by the program. This is why certain effect interpreters can't be used together: one requires
a primitive effect that can't be threaded by the other. You can look at the documentation of a threading constraint to see what
primitive effects it may accept. Threading constraints are placed with the help of Threaders
.
To clarify how primitive effects work, consider the interpreter
bracketToIO :: (Carrier m, MonadMask m)
=> BracketToIOC m a
-> m a
which interprets the Bracket
effect. What this actually means is that BracketToIOC
adds upon the derived effects of m
-- Derivs m
-- with that effect:
Derivs (BracketToIOC m) = Bracket ': Derivs m
What underlying effects a program may have access to is determined by Derivs
, and because BracketToIOC
extends upon it, this means that the program passed to bracketToIO
can make use of actions of Bracket
.
In a similar way, interpreters may also add effects to the list of primitive effects of m
-- Prims m
.
In this case, the only way bracketToIO
can interpret Bracket
is if it has direct access to m
in the handler, so it may use the methods of MonadMask m
. So Bracket
is also added as a primitive effect:
Prims (BracketToIOC m) = Bracket ': Prims m
Note that effects in Prims
don't have to directly match an effect in Derivs
. For example, runError
makes use of Optional ((->) e)
as a primitive effect to interpret Catch e
, but doesn't expose Optional ((->) e)
as a derived effect. How this works is discussed later in helper primitive effects.
Despite their similarities, Prims
is very different from Derivs
. Adding derived effects provides a benefit to the user of an interpreter -- adding primitive effects does not:
- More effects in
Derivs
means greater variety of effects a program may use. More effects inPrims
means lesser variety of interpreters a program may use. - Interpreters add effects in
Derivs
to provide power to the program. Interpreters add effects inPrims
only to provide power to themselves. - Once an effect of
Derivs
is consumed by an interpreter, the program can no longer make use of it. Once an effect ofPrims
is consumed by an interpreter, then the program is no longer restricted by it.
Sometimes, users also need higher-order access to the current monad for the interpretation of their own effects. However, interpreting user-defined effects as primitives is problematic, because primitive effects suffer from the O(n2) instances problem. In fact, the hope is that users never have to do this. Instead, if the need arises, users are intended to make use of helper primitive effects to gain the power they need to interpret their own effects.
Various combinators involving primitive effects are offered by the Control.Effect.Primitive
module.
Helper primitive effects are effects designed for the purpose of providing the power necessary to interpreters so that user-defined
primitive effects aren't necessary.
In ascending order of power, the helper primitive effects offered by this library are: Regional
, Optional
, BaseControl
, and Unlift
.
The reason there are so many is because carriers differ in how many of these they may thread. For example, of these,
ContThreads
accepts only Regional
and Optional
; WriterThreads
also accepts BaseControl
; and ReaderThreads
is the only threading
constraint that accepts Unlift
.
Let's take an example. Let's assume ErrorIO
doesn't exist, and you want to implement the following:
import qualified Control.Monad.Catch as C
runErrorAsExc :: (Exception e, Carrier m, C.MonadCatch m) => ErrorAsExcC e m a -> m a
Which interprets both Throw e
and Catch e
by simply using e
as an IO exception and
using the methods of MonadCatch
in order to throw
and catch
it.
We'll also be adding a ReaderThreads
threading constraint to this so we may use -Simple
interpreters.
How would you go about this? First, let's try to use interpretSimple
:
type ErrorAsExcC e = CompositionC
'[ InterpretSimpleC (Catch e)
, InterpretSimpleC (Throw e)
]
-- Derivs (ErrorAsExcC e m) = Catch e ': Throw e ': Derivs m
-- Prims (ErrorAsExcC e m) = Prims m
runErrorAsExc :: ( Exception e
, Carrier m
, C.MonadCatch m
, Threaders '[ReaderThreads] m p
)
=> ErrorAsExcC e m a -> m a
runErrorAsExc =
interpretSimple (\case
Throw e -> liftBase $ C.throw e
)
. interpretSimple (\case
Catch m h -> m `C.catch` h -- oops
)
. runComposition
This doesn't work. That is because the environment inside interpretSimple
doesn't work on m
, it works on any carrier z
that
shares the same effects as m
, and also lifts m
. This is enough to implement throw
, but not catch
.
One solution is to interpret Catch
here as a primitive effect using interpretPrimSimple
(or interpretPrim
, or interpretPrimViaHandler
), which allows you to operate on m
directly:
type ErrorAsExcC e = CompositionC
'[ InterpretPrimSimpleC (Catch e)
, InterpretSimpleC (Throw e)
]
-- Derivs (ErrorAsExcC e m) = Catch e ': Throw e ': Derivs m
-- Prims (ErrorAsExcC e m) = Catch e ': Prims m
runErrorAsExc :: ( Exception e
, Carrier m
, C.MonadCatch m
, Threaders '[ReaderThreads] m p
)
=> ErrorAsExcC e m a -> m a
runErrorAsExc =
interpretSimple (\case
Throw e -> liftBase $ C.throw e
)
. interpretPrimSimple (\case
Catch m h -> m `C.catch` h
)
. runComposition
But this is no good. Catch
is not intended to be used as a primitive effect, and doesn't have any ThreadsEff
instances defined for it.
This makes this interpretation unusable in practice! In fact, this won't actually compile, since the ReaderThreads
threading constraint
-- which is necessary for the -Simple
variants we're using here -- doesn't accept Catch
as a primitive effect.
What we can do instead is to make use of a helper primitive effect. The perfect fit here is Optional
:
data Optional s m a where
Optionally :: s a -> m a -> Optional s m a
Optional
has ThreadsEff
instances defined for almost every underlying monad transformer used in the library, as long as s
is a functor. If we choose s = (->) e
, this becomes:
data Optional ((->) e) m a where
Optionally :: (e -> a) -> m a -> Optional ((->) e) m a
Awfully similar to catch. In fact, we could implement catch using this:
catch' :: Eff (Optional ((->) e)) m => m a -> (e -> m a) -> m a
catch' m h = join $ optionally h (fmap pure m)
If you're not convinced that this is actually safe (it does look awfully suspicious), here's a more obviously safe implementation of try
:
try' :: Eff (Optional ((->) e) m => m a -> m (Either e a)
try' m = optionally Left (fmap Right m)
which you can use to implement catch
:
catch' :: Eff (Optional ((->) e)) m => m a -> (e -> m a) -> m a
catch' m h = try' m >>= either h return
Let's use Optional ((->) e)
as our primitive effect instead. We'll interpret Catch
in terms of it, and then
interpret Optional ((->) e)
using interpretPrimSimple
in terms of MonadCatch
's catch
:
type ErrorAsExcC e = CompositionC
'[ ReinterpretSimpleC (Catch e) '[Optional ((->) e)]
, InterpretPrimSimpleC (Optional ((->) e))
, InterpretSimpleC (Throw e)
]
-- Derivs (ErrorAsExcC e m) = Catch e ': Throw e ': Derivs m
-- Prims (ErrorAsExcC e m) = Optional ((->) e) ': Prims m
runErrorAsExc :: ( Exception e
, Carrier m
, C.MonadCatch m
, Threaders '[ReaderThreads] m p
)
=> ErrorAsExcC e m a -> m a
runErrorAsExc =
interpretSimple (\case
Throw e -> liftBase $ C.throw e
)
. interpretPrimSimple (\case
Optionally h m -> m `C.catch` (return . h)
)
. reinterpretSimple (\case
Catch m h -> join $ optionally h (fmap pure m)
)
. runComposition
By using Optional
as our primitive effect, we still gain the access to the current monad we need
without having to treat Catch
as a primitive effect: only Optional
, which already
has ThreadsEff
instances defined for it. This scales to your own user-defined effects,
and you may choose as powerful helper primitive effects as you need to interpret them (but as weak as possible
so that you may use a larger variety of interpreters in your program).
Regional
and Optional
are special in they are more general than they have to be. They have two specializations
respectively -- Hoist
and HoistOption
-- that are as powerful as their general forms could ever be. Here's how
runErrorAsExc
can be rewritten to use HoistOption
instead:
type ErrorAsExcC e m = CompositionC
'[ IntroC '[Catch e, Throw e] '[HoistOption m]
, InterpretSimpleC (Catch e)
, InterpretSimpleC (Throw e)
, HoistOptionC
]
runErrorAsExc :: ( Exception e
, Carrier m
, C.MonadCatch m
, Threaders '[ReaderThreads] m p
)
=> ErrorAsExcC e m m a -> m a
runErrorAsExc =
runHoistOption
. interpretSimple (\case
Throw e -> liftBase $ C.throw e
)
. interpretSimple (\case
Catch m h -> join $
hoistOption
(\exit m' -> m' `C.catch` (return . exit . h)
(fmap pure m)
)
. introUnderMany
. runComposition
This isn't as clean, however. Note now that m
must be provided two times to ErrorAsExcC
so
that it may use it inside of the type synonym (the two m
s can be unified into one, but that would prevent
the use of ErrorAsExcC
inside of other CompositionC
s). Also, runHoistOption
must be at the very end,
so introUnderMany
is required to move the HoistOption m
effect to after the Throw e
effect.
It's because of these issues that Regional
and Optional
are as general as they are.
Bracket can also be used as a helper primitive effect.
Of special note is the interpreter runBracketLocally
, which is rather unusual. Unlike most interpreters
of a primitive effect, runBracketLocally
makes no use of its direct access to the current monad:
it interprets a use of Bracket
the same way ignoreBracket
does. The difference is that since it
establishes Bracket
as a primitive effect, carriers need to thread it -- and carriers that thread
Bracket
are expected to invoke the destructor if they were to make any abortive computations of their own.
For example, ExceptT e
threads Bracket
by making sure to invoke the destructor even if the use
portion
of generalBracket
returns Left e
.
Because of that, although runBracketLocally
does nothing on the surface, by forcing carriers to thread
its uses of the Bracket
effect it effectively protects against abortive computations of any effect local
relative to it. Hence the name runBracketLocally
.
An interesting example of runBracketLocally
is how it can be used to make
a safe interpretation of Writer s
using it and runState
:
type WriterUsingStateBracketC s = CompositionC
'[ IntroC '[Pass s, Listen s, Tell s] '[Bracket, State s]
, InterpretSimpleC (Pass s)
, InterpretSimpleC (Listen s)
, InterpretSimpleC (Tell s)
, BracketLocallyC
, StateC s
]
runWriterUsingStateBracket
:: ( Monoid s
, Carrier m
, Threaders '[StateThreads, ReaderThreads] m p
)
=> WriterUsingStateBracketC s m a
-> m (s, a)
runWriterUsingStateBracket =
runState mempty
. runBracketLocally
. interpretSimple (\case
Tell s -> modify' (<> s)
)
. interpretSimple (\case
Listen m -> do
sInit <- get
put mempty
a <- m `onError` modify' (sInit <>)
sLocal <- get
put $! sInit <> sLocal
return (sLocal, a)
)
. interpretSimple (\case
Pass m -> do
sInit <- get
put mempty
(f, a) <- m `onError` modify' (sInit <>)
sLocal <- get
put $! sInit <> f sLocal
return a
)
. introUnderMany
. runComposition
In order to interpret Listen
and Pass
, runWriterUsingStateBracket
temporarily
resets the state to mempty
so that it may observe how the argument computation modifies it.
This would be unsafe without runBracketLocally
: the computation may throw an exception of a local effect,
and then the state will never get restored (exceptions of global effects don't matter since they would revert
the state anyway, since we're interpreting the state using runState
).
By using runBracketLocally
and onError
, we ensure that if any local effect throws an exception, then the
state will be restored before letting the exception go through.
The worst-case scenario happens: you have some effect whose interpretation requires direct access to the current monad, and the helper primitive effects available are either too weak, or too strong. You want to use some interpreters in your interpretation stack whose carriers could, in theory, thread your effect, but can't thread the more powerful helper primitive effects that you'd be forced to use.
In this case, when all else fails, you can interpret your effect as a primitive effect.
The hope is that this is never necessary. If it ever is, then that's a failing of the library: please make
an issue about it. Tell us the effect you needed to interpret as a primitive, and why you couldn't use the stronger helper
primitive effects (Unlift
should be powerful enough for any purpose, so it'd have to be because it disallows
too many interpreters from being used). We'll try, if possible, to generalize your usage and add it as a helper
primitive effect to the library.
User-defined primitive effects are straight-forward. Interpret them using interpretPrim
, interpretPrimSimple
,
or interpretPrimViaHandler
and PrimHandler
, then add ThreadsEff
instances for every monad transformer that
has a corresponding threading constraint that is able to thread your effect. For example, ErrorThreads
corresponds to ExceptT
, so you should make a ThreadsEff (ExceptT e) YourEffect
instance if you can.
You don't have to add ThreadsEff
instances for carriers or IdentityT
.
The only problem is that those ThreadsEff
instances are still a lot
of boilerplate, and when writing them, you'll be living in the bad old days of mtl
at its worst.
Split interpretation is a trick that allows you to side-step the most serious problems you may run into when using interpreters. Split interpretation is called such because it relies on splitting the interpretation stack into multiple branches.
Let's say you have the following pieces of the program:
doSomeConcStuff :: Effs '[Ask GlobalConfig, Conc] m
=> String -> m Bool
mainProgram :: Effs '[Ask GlobalConfig, Cont] m
=> m String
and you need to make use of doSomeConcStuff
inside mainProgram
. The easy way to do this is to extend mainProgram
's Effs
with Conc
so that it may call doSomeConcStuff
, but there's a problem with that approach: there is no combination of interpreters for Conc
and Cont
that can be used together. They're essentially incompatible effects. This wouldn't compile:
main :: IO String
main =
runM @IO
$ runAskConstSimple globalConfig
$ concToIO
$ runCont
$ mainProgam
You don't need to make use of Cont
in doSomeConcStuff
, and you don't need Conc
in mainProgram
except for doSomeConcStuff
, so the two effects will never interact; and yet, in-other-words
won't allow you to use both because you can't actually prove that.
Split interpretation provides you with a way to do just that. The trick is to create an effect for doSomeConcStuff
, and use that in mainProgram
:
data DoSomeConcStuff :: Effect where
DoSomeConcStuff :: String -> DoSomeConcStuff m Bool
doSomeConcStuff :: Eff DoSomeConcStuff m => String -> m Bool
doSomeConcStuff str = send (DoSomeConcStuff str)
doSomeConcStuffImplementation
:: Effs '[Ask GlobalConfig, Conc] m
=> String -> m Bool
mainProgram :: Effs
'[ Ask GlobalConfig
, Cont
, DoSomeConcStuff
] m
=> m String
And now, during interpretation, you can interpret DoSomeConcStuff
in terms of doSomeConcStuffImplementation
, by using concToIO
inside of the handler! In order to be able to do that, you need to have access to m
-- because of concToIO
's MonadBaseControlPure IO
constraint -- but fortunately, EffHandler
s have the ability to lift values of m
to the hidden carrier inside of the effect handler by using liftBase
.
runDoSomeConcStuff
:: ( Eff (Ask GlobalConfig) m
, MonadBaseControlPure IO m
)
=> SimpleInterpreterFor DoSomeConcStuff m
runDoSomeConcStuff = interpretSimple $ \case
DoSomeConcStuff str -> liftBase $ concToIO $ doSomeConcStuffImplementation str
main :: IO String
main =
runM @IO
$ runAskConstSimple globalConfig
$ runDoSomeConcStuff -- Important to place this after runCont
$ runCont
$ mainProgam
This way, you can make use of both Cont
and Conc
in the same program -- even though they're incompatible -- by
splitting interpretation such that they're never used together.
Note that this doesn't work if doSomeConcStuff
were higher-order, because then you wouldn't be able to interpret
DoSomeConcStuff
through using liftBase
. This makes sense, because if doSomeConcStuff
were higher-order, then
there'd be no way to guarantee that mainProgram
wouldn't smuggle in a computation to doSomeConcStuff
that would do some Cont
nastiness -- which Conc
can't play nicely with.
This trick is easily adaptable to already existing effects which can let you get rid of primitive effects. Say you already have the following:
data DoBracketStuff m a where
DoBracketStuff :: String -> DoBracketStuff m Int
doBracketStuffImplementation :: Eff Bracket m => String -> m Int
doBracketStuffToBracket :: Eff Bracket m => SimpleInterpreterFor DoBracketStuff m
doBracketStuffToBracket = interpretSimple $ \case
DoBracketStuff str -> doBracketStuffImplementation str
If Bracket
is going to be interpreted using bracketToIO
(or runBracketLocally
) down the line, then that will incur Bracket
as a primitive effect, even though you're only using it for the implementation of a first-order effect. By applying split interpretation and doing bracketToIO
inside the handler of DoBracketStuff
, you can get rid of Bracket
as a primitive effect for the rest of the program.
doBracketStuffToIO :: (Carrier m, MonadMask m) => SimpleInterpreterFor DoBracketStuff m
doBracketStuffToIO = interpretSimple $ \case
DoBracketStuff str -> liftBase $ bracketToIO $ doBracketStuffImplementation str
Note that this does place a MonadMask
constraint, like bracketToIO
, but since it no longer imposes Bracket
as a primitive effect you can simply run this after any interpreter whose carrier can't lift MonadMask
.
One of the largest issues with in-other-words
is the problematic nature of using interpreters that emit threading constraints inside of application code. Fortunately, split interpretation makes this much less of an issue than it could be.
Consider the following program:
doLocalStateStuff
:: Effs '[Ask GlobalConfig, State Int] m
=> m Bool
mainProgram :: ( Eff (Ask GlobalConfig) m
, Threaders '[StateThreads] m p
)
=> m String
mainProgram = do
...
(endLocalState, res) <- runState initLocalState doLocalStateStuff
...
The use of runState
here is painful. It generates a threading constraint that needs to be propagated throughout the program, and may end up not being satisfied due to some primitive effect down the line. It also chooses a specific implementation of a state interpreter at the use-site, when all the program really cares about is having the ability to run state locally in some way.
A workaround to this issue is to make doLocalStateStuff
-- taking its initial state and returning the final state -- into a new effect.
data DoLocalStateStuff :: Effect where
DoLocalStateStuff :: Int -> DoLocalStateStuff m (Int, Bool)
doLocalStateStuff :: Eff DoLocalStateStuff m => Int -> m (Int, Bool)
doLocalStateStuff init = send DoLocalStateStuff
doLocalStateStuffImplementation
:: Effs '[Ask GlobalConfig, State Int] m
=> m Bool
mainProgram :: Effs
'[ Ask GlobalConfig
, DoLocalStateStuff
] m
=> m String
mainProgram = do
...
(endLocalState, res) <- doLocalStateStuff initLocalState
...
This way, you can decide what State
interpretation to use at interpretation time (outside of application code) without any issues:
doLocalStateStuffToIO
:: Effs [Ask GlobalConfig, Embed IO] m
=> SimpleInterpreterFor DoLocalStateStuff m
doLocalStateStuffToIO = interpretSimple $ \case
DoLocalStateStuff initState -> stateToIO initState doLocalStateStuffImplementation
runDoLocalStateStuff
:: ( Eff (Ask GlobalConfig) m
, Threaders '[StateThreads] m p
)
=> SimpleInterpreterFor DoLocalStateStuff m
runDoLocalStateStuff = interpretSimple $ \case
DoLocalStateStuff initState -> runState initState doLocalStateStuffImplementation
main :: IO String
main =
runM @IO
$ runAskConstSimple globalConfig
$ doLocalStateStuffToIO -- or runDoLocalStateStuff
$ mainProgam
Note that unlike the other examples, these interpretations don't make use of liftBase
, meaning DoLocalStateStuff
could be higher-order if it needs to be (using lift
in the interpretations as necessary). This doesn't work for every interpreter, however: say we instead had DoLocalErrorStuff
and wanted doLocalErrorStuffToIO
. errorToIO
has a MonadCatch
constraint, so if we want to use that to implement doLocalErrorStuffToIO
, we would need to use liftBase
, so DoLocalErrorStuff
better not be higher-order. This can sometimes be worked around; interpreters that place constraints on the carrier sometimes have an alternative version that relies on an effect insted. For errorToIO
, that alternative interpreter is errorToErrorIO
.
By using that, you avoid placing the MonadCatch
constraint, and thus you don't need to use liftBase
. This comes at a cost: you need to run errorIOToIO
somewhere in your interpretation stack, and errorIOToIO
imposes a primitive effect. So if you can use liftBase
with errorToIO
instead, you probably should.
Split interpretation can be used to solve both the problems of incompatible effects and abstract effect interpretation simultaneously. NonDet
is another effect which can't gel with Conc
, but if you only need it within a region, you can do this:
data DoLocalNonDetStuff m a where
DoLocalNonDetStuff :: String -> DoLocalNonDetStuff m [Int]
doLocalNonDetStuff :: Eff DoLocalNonDetStuff m => String -> m [Int]
doLocalNonDetStuff str = send (DoLocalNonDetStuff str)
doLocalNonDetStuffImplementation
:: Effs [Ask GlobalConfig, NonDet] m
=> String -> m Int
mainProgram :: Effs
'[ Ask GlobalConfig
, DoLocalNonDetStuff
, Conc
] m
=> m String
mainProgram = do
...
results <- doLocalNonDetStuff arg
...
runDoLocalNonDetStuff :: ( Eff (Ask GlobalConfig) m
, Threaders [NonDetThreads] m p
)
=> SimpleInterpreterFor DoLocalNonDetStuff m
runDoLocalNonDetStuff = interpretSimple $ \case
DoLocalNonDetStuff str -> runNonDet @[] (doLocalNonDetStuffImplementation str)
main :: IO String
main =
runM @IO
$ runAskConstSimple globalConfig
$ runDoLocalNonDetStuff -- Important to place this after concToIO
$ concToIO
$ mainProgam
RepresentationalEff
is the minimal requirement for an effect to be an effect: it means that the effect e m a
is representational in m
, meaning if you have monads m
and n
that have the same internal representation, then e m a
and e n a
have the same internal representation.
What this in essence corresponds to is that you put no constraints upon m
in your effect, and m
is not present in the returned value of an action of the effect.
GHC derives RepresentationalEff
automatically for any effects, so you never have to make instances of your own. It could happen, however, that some effect you define will turn out to not be representational in m
. What do you do then?
You can check if your effect is representational by checking :info YourEffect
in GHCi. If you get a type role
message where the second-to-last parameter says nominal
, then your effect is not representational. Otherwise, it is. For example:
data NaiveLayer s :: Effect where
NaiveLayer :: m s -> NaiveLayer s m (m s)
If you do :info NaiveLayer
, you get
type role NaiveLayer nominal nominal nominal
And since the second-to-last parameter is nominal
(the one corresponding to m
), this effect is not representational, and thus not valid.
In this example, the reason this is not representational is that m
is present in the return value. The solution is really simple: add a function to transform the result inside the action, so that m
is not present in the result:
data Layer s :: Effect where
Layer :: (m s -> res) -> m s -> Layer s m res
This is equivalent to NaiveLayer
, since you can do:
layer :: Eff (Layer s) m => m s -> m (m s)
layer m = send (Layer id m)
And interpretation just has to apply the provided function before giving back the result.
The difference is that Layer
is representational. :info Layer
gives:
type role Layer nominal representational representational
And so your effect is saved.
Effects that place constraints on m
are more difficult to save, and can't always be done.
Let's consider the BaseControl
effect. The naive implementation of it would be this:
data BaseControl b :: Effect where
BaseControl :: (MonadBaseControl b m => m a) -> BaseControl b m a
This is not representational because of the constraint placed on m
inside of the function. The solution is to use Coercible
so the constraint
is placed on a different monad which is coercible to m
:
data BaseControl b :: Effect where
BaseControl :: (forall z. (Coercible z m, MonadBaseControl b z) => Proxy z -> m a) -> BaseControl b m a
Coercible
is an exception to the rule: placing a Coercible
constraint on m
won't make BaseControl
not representational.
This solution does make BaseControl
more difficult to use and interpret. You'll have to figure out tricks to not make this internal machinery visible to the user. The implementation of BaseControl
that in-other-words
provides uses coerce
together with an action that makes use of a custom carrier (see GainBaseControlC
in the source code of Control.Effect.BaseControl
).
If you want to place a constraint on m
as part of the GADT constructor, you can use Coercible
on an existential. For example, instead of
data Zippy :: Effect where
Zippy :: MonadZip m => m a -> m b -> Zippy m (a, b)
You can do:
data Zippy :: Effect where
Zippy :: (MonadZip z, Coercible z m) => z a -> z b -> Zippy m (a, b)
and still be able to create the action:
zippy :: (Eff Zippy m, MonadZip m) => m a -> m b -> m (a, b)
zippy ma mb = send (Zippy ma mb)
Interpreters of Zippy
will then have to coerce
the provided arguments in order to transform them to
the Carrier
the interpreter is expected to work with. For example:
interpretSimple @Zippy $ \case
Zippy ma mb -> coerce (mzip ma mb)
If the mix of InterpretC
, IntroC
, CompositionC
and friends aren't good enough for your purposes, you may want to look into creating your own carriers. This can get surprisingly difficult, so try to primarily use the tools offered in Control.Effect
.
The tools needed to create your own Carrier
instances are offered in Control.Effect.Carrier
.
Defining Carrier
instances for simple newtypes of existing carriers is relatively easy, but tedious. No matter what the newtype is, you will want to derive as many as possible of the type classes that users of or interpreters in in-other-words
may make use of. Control.Effect.Carrier
re-exports the names of the following type classes for the purposes of newtype deriving:
Alternative, MonadPlus
, MonadFix, MonadFail, MonadIO
, MonadThrow, MonadCatch, MonadMask
, MonadBase, MonadBaseControl
, MonadTrans, MonadTransControl
Deriving Carrier
may require additional measures. In the simple case of:
newtype NewtypeWrapperC m a = NewtypeWrapperC (m a)
You can simply newtype-derive Carrier
. Control.Effect.Carrier
also exports IdentityT
so you can derive MonadTrans
and MonadTransControl
via IdentityT
for these kinds of newtype wrappers.
For newtypes that transform the wrapped m
, things get more complicated. For example, for:
newtype ErrorStateC m a = ErrorStateC (ErrorC String (StateC Int m) a)
You must standalone newtype-derive the Carrier
instance, and that instance requires the constraints necessary to run the interpreters corresponding to the carriers used. So as ErrorStateC
uses ErrorC
(runError
) and StateC
(runState
), deriving a newtype instance of Carrier
for ErrorStateC
can be done as follows:
deriving newtype instance (Carrier m, Threaders '[ErrorThreads, StateThreads] m p)
=> Carrier (ErrorStateC m)
You may instead want to define a Carrier
instance manually, instead of deriving it. How to do this is detailed in the next section.
If you want to create a Carrier
that is not a simple newtype over an existing carrier, but uses a novel monad transformer, then you have to make a Carrier
instance manually.
A Carrier m
must define the associated derived effects Derivs m
and primitive effects Prims m
corresponding to the carrier, as well as the two methods algPrims
and reformulate
. For further reading, see The Inner Workings of the Library.
We'll be exploring how to make two carriers, both based on the underlying monad transformer:
newtype ChurchExceptT e m a = ChurchExceptT {
runChurchExceptT :: forall r. (e -> m r) -> (a -> m r) -> m r
}
instance Monad m => Monad (ChurchExceptT e m) where
return a = ChurchExceptT $ \_ right -> right a
m >>= f = ChurchExceptT $ \left right ->
runChurchExceptT m left $ \a ->
runChurchExceptT (f a) left right
instance MonadTrans (ChurchExceptT e) where
lift m = ChurchExceptT $ \_ right -> m >>= right
throwE :: e -> ChurchExceptT e m a
throwE e = ChurchExceptT $ \left _ -> left e
catchE :: ChurchExceptT e m a -> (e -> ChurchExceptT e m a) -> ChurchExceptT e m a
catchE m h = ChurchExceptT $ \left right ->
runChurchExceptT (\e -> runChurchExceptT (h e) left right) right m
One of the Carrier
s will be ChurchThrowC
, which simply implements the Throw
effect, and the other Carrier
will be ChurchErrorC
, which expands on ChurchThrowC
by also providing a Catch
effect. The reason why these are seperated is that ChurchErrorC
will also impose a primitive effect in order to perform its catches.
Starting with ChurchThrowC
:
newtype ChurchThrowC e m a = ChurchThrowC {
unChurchThrowC :: ChurchExceptT e m a
}
deriving (Functor, Applicative, Monad, MonadTrans, ...)
instance Carrier m => Carrier (ChurchThrowC e m) where
type Derivs (ChurchThrowC e m) = Throw e ': Derivs m
type Prims (ChurchThrowC e m) = Prims m
algPrims = ...
reformulate = ...
Control.Effect.Carrier
provides a variety of combinators for defining algPrims
and reformulate
. We'll begin by using them to define reformulate
.
We have access to:
reformulate @m
:: Reformulation
(Derivs m)
(Prims m)
m
We need to define:
reformulate @(ChurchThrowC e m)
:: Reformulation
(Throw e ': Derivs m)
(Prims m)
(ChurchThrowC e m)
First of all, we have liftReform
, which allows you to lift the monad parameter of a Reformulation
. This allows us to get
liftReform (reformulate @m)
:: Reformulation
(Derivs m)
(Prims m)
(ChurchThrowC e m)
Now, we need to add Throw e
as a derived effect. addDeriv
is an analogue to intepretSimple
that allows you to do this. Its type signature is:
addDeriv :: ( RepresentationalEff e
, Monad m
)
=> ( forall z x
. ( Carrier z
, Prims z ~ p
, Derivs z ~ r
, MonadBase m z
)
=> e (Effly z) x -> Effly z x
)
-> Reformulation r p m
-> Reformulation (e ': r) p m
Don't be overwhelmed: it's similar to the type signature of interpretSimple
(with EffHandler
). In particular, note the MonadBase m z
constraint inside the handler, which allows you to lift first-order operations. We can use this to lift throwE
as defined earlier:
addDeriv (\case
Throw e -> liftBase $ ChurchThrowC $ throwE e
)
$ liftReform
$ reformulate @m
And this completes our definition of reformulate
; this has the desired type signature
Reformulation (Throw e ': Derivs m) (Prims m) (ChurchThrowC e m)
Let's move on to algPrims
. We need to construct:
algPrims @(ChurchThrowC e m)
:: Algebra (Prims m) (ChurchThrowC e m)
given
algPrims @m
:: Algebra (Prims m) m
If we were simply dealing with a newtype of m
, we could set algPrims = coerce (algPrims @m)
, but since we're transforming m
, it's not quite that simple. In fact, it's clear that this can't be done with what we currently have access to. This is the problem with primitive effects: their handlers need to be lifted on a transformer-by-transformer basis.
This is gone about by defining ThreadsEff
instances for the relevant monad transformer and each relevant effect. So in order to lift algPrims
, we need to establish that ThreadsEff
instances exist for the relevant monad transformer for each effect of Prims m
. Threads
does just that, and provides:
thread :: (Threads t p, Monad m)
=> Algebra p m
-> Algebra p (t m)
The "relevant monad transformer" in this case is ChurchExceptT
. So if we add the Threads (ChurchExceptT e) (Prims m)
constraint to our instance, we gain access to
thread :: Algebra (Prims m) m -> Algebra (Prims m) (ChurchExceptT e m)
to which we can provide algPrims @m
to get
Algebra (Prims m) (ChurchExceptT e m)
Finally, since ChurchThrowC
is a newtype over ChurchExceptT
, we can coerce
this to get
Algebra (Prims m) (ChurchThrowC e m)
The final definition is:
algPrims = coerce (thread @(ChurchExceptT e) (algPrims @m))
and the final instance is:
instance ( Carrier m
, Threads (ChurchExceptT e) (Prims m)
)
=> Carrier (ChurchThrowC e m) where
type Derivs (ChurchThrowC e m) = Throw e ': Derivs m
type Prims (ChurchThrowC e m) = Prims m
algPrims = coerce (thread @(ChurchExceptT e) (algPrims @m))
reformulate =
addDeriv (\case
Throw e -> liftBase $ ChurchThrowC $ throwE e
)
$ liftReform
$ reformulate
And we're done.
Now, let's move on to ChurchErrorC
. As shown in Helper primitive effects, we need a primitive effect, since we're not interpreting the higher-order Catch
in terms of other effects, and Optional ((->) e)
is the perfect pick:
newtype ChurchErrorC e m a = ChurchErrorC {
unChurchErrorC :: ChurchExceptT e m a
}
deriving (Functor, Applicative, Monad, MonadTrans, ...)
instance ( Carrier m
, Threads (ChurchExceptT e) (Prims m)
)
=> Carrier (ChurchErrorC e m) where
type Derivs (ChurchErrorC e m) = Catch e ': Throw e ': Derivs m
type Prims (ChurchErrorC e m) = Optional ((->) e) ': Prims m
algPrims = ...
reformulate = ...
Let's once again begin with reformulate
. Note that the tail end of our effect stack is identical to that of ChurchThrowC
's; and since both ChurchErrorC
and ChurchThrowC
are newtypes over ChurchExceptT
, we can actually repurpose reformulate
of ChurchThrowC
by coercing it with the help of coerceReform
:
coerceReform (reformulate @(ChurchThrowC e m))
:: Reformulation
(Throw e ': Derivs m)
(Prims m)
(ChurchErrorC e m)
Now, we want to add Catch e
as a derived effect; problem is, we want to interpret it in terms of Optional ((->) e)
, and that isn't present in the derived effects, here. Because of that, we'll use addPrim
to add Optional ((->) e)
as a primitive effect, which also gives us access to it as a derived effect:
addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
:: Reformulation
(Optional ((->) e) ': Throw e ': Derivs m)
(Optional ((->) e) ': Prims m)
(ChurchErrorC e m)
And now we're free to add Catch e
as a derived effect, which makes use of Optional
:
addDeriv (\case
Catch m h -> join $ optionally h (fmap pure m)
)
$ addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
:: Reformulation
(Catch e ': Optional ((->) e) ': Throw e ': Derivs m)
(Optional ((->) e) ': Prims m)
(ChurchErrorC e m)
Now we've provided both Throw
and Catch
as derived effects, but the type signature still isn't quite what we need it to be. We shouldn't expose that Optional ((->) e)
as a derived effect; we needed it as such to interpret Catch
, but to the outside user, it should only be visible as a primitive effect. To fix that, we can make use of weakenReformUnderMany
, which allows us to remove derived effects from a reformulation:
-- v The top effects of the stack before the effects to remove
weakenReformUnderMany @'[Catch e] @'[Optional ((->) e)]
-- ^ What effects to remove
$ addDeriv (\case
Catch m h -> join $ optionally h (fmap pure m)
)
$ addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
:: Reformulation
(Catch e ': Throw e ': Derivs m)
(Optional ((->) e) ': Prims m)
(ChurchErrorC e m)
Both of the type applications to weakenReformUnderMany
are needed. But since we're only have one effect on the top of the stack before the effects to remove, we can actually use the simpler weakenReformUnder
, which lets us omit the first type application:
-- v What effects to remove
weakenReformUnder @'[Optional ((->) e)]
$ addDeriv (\case
Catch m h -> join $ optionally h (fmap pure m)
)
$ addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
:: Reformulation
(Catch e ': Throw e ': Derivs m)
(Optional ((->) e) ': Prims m)
(ChurchErrorC e m)
In fact, since we're only removing one effect, we can use weakenReformUnder1
, which allows us to get rid of the other type application.
weakenReformUnder1
$ addDeriv (\case
Catch m h -> join $ optionally h (fmap pure m)
)
$ addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
:: Reformulation
(Catch e ': Throw e ': Derivs m)
(Optional ((->) e) ': Prims m)
(ChurchErrorC e m)
And we're done with reformulate
.
algPrims
is actually easier in comparison. As with reformulate
, we can begin with repurposing algPrims
for ChurchThrowC
:
coerce (algPrims @(ChurchThrow e m)) :: Algebra (Prims m) (ChurchErrorC e m)
Now, we need to add a handler for Optional ((->) e)
onto this. This is done through powerAlg
:
powerAlg :: Algebra r m
-> (forall x. e m x -> m x)
-> Algebra (e ': r) m
And the handler is based on using catchE
:
powerAlg (coerce (algPrims @(ChurchThrow e m))) $ \case
Optionally h m -> ChurchErrorC $
unChurchErrorC m `catchE` (return . h)
And we're done. The final instance is as follows:
instance ( Carrier m
, Threads (ChurchExceptT e) (Prims m)
)
=> Carrier (ChurchErrorC e m) where
type Derivs (ChurchErrorC e m) = Catch e ': Throw e ': Derivs m
type Prims (ChurchErrorC e m) = Optional ((->) e) ': Prims m
algPrims = powerAlg (coerce (algPrims @(ChurchThrow e m))) $ \case
Optionally h m -> ChurchErrorC $
unChurchErrorC m `catchE` (return . h)
reformulate =
weakenReformUnder1
$ addDeriv (\case
Catch m h -> join $ optionally h (fmap pure m)
)
$ addPrim
$ coerceReform
$ reformulate @(ChurchThrowC e m)
Although the instance is done, this still isn't enough to use these carriers in practice. Since the two carriers make use of a completely new monad transformer in the form of ChurchExceptT
, you need to define ThreadsEff
instances for it over all the various primitive effects so that the Threads (ChurchExceptT e) (Prims m)
constraint can actually be satisfied. You also likely want to make a threading constraint for it, which the interpreters making use of these carriers should emit. In this case, the threading constraint should be:
class (forall e. Threads (ChurchExceptT e) p) => ChurchErrorThreads p
instance (forall e. Threads (ChurchExceptT e) p) => ChurchErrorThreads p
This is a lot of boilerplate, and there's no way to avoid it in this case. Of course, if you're using a completely novel monad transformer, you're probably not a typical user, but rather a library writer/contributer and can bear to do it.
Two of the most complicated effects offered by the library -- and among the most powerful -- are Intercept
and its brother InterceptCont
.
These effects allow you to modify how actions of a specific first-order effect are executed within a region.
These effects serve a very specific niche: defining a class of higher-order effects that even mtl
would have serious issues with.
Outside of that, you should try to avoid using Intercept
. Its complexity typically isn't worth it.
Imagine the following effect:
data Editorialized o :: Effect where
Submit :: o -> Editorialized o m ()
Edit :: (o -> m (Maybe o)) -> m a -> Editorialized o m a
The intent here is that when you call edit
upon a region, the passed action will be called at each point submit
is called within the region,
which may use effects of m
in order to study, modify, and/or reject each submit
ted o
.
Believe it or not, using Intercept
is really the only good way to define an interpreter for this effect! The trick is to interpret it in terms of a first order effect and interceptions on that effect. In this case, the first-order effect of choice is rather obvious: Tell o
. Here's how an editorializedToTell
interpreter would look like:
type EditorializedToTellC o = CompositionC
'[ ReinterpretSimpleC (Editorialized o)
'[InterceptCont (Tell o), Intercept (Tell o), Tell o]
, InterceptContC (Tell o)
]
editorializedToTell :: forall o m a p
. ( Eff (Tell o) m
, Threaders '[SteppedThreads, ReaderThreads] m p
)
=> EditorializedToTellC o m a -> m a
editorializedToTell =
runInterceptCont
. reinterpretSimple (\case
Submit o -> tell o
Edit f m ->
intercept @(Tell o)
(\(Tell o) -> f o >>= \case
Just o' -> tell o'
Nothing -> pure ()
)
m
)
. runComposition
This seems simple, but there are a lot of things to keep in mind here.
-
runInterceptCont @eff
interprets three effects:InterceptCont eff
,Intercept eff
, andeff
. In this case (whereeff = Tell o
), we prevent all three from being exposed (usingreinterpretSimple
) to the outside world. - Because we hide the
Tell o
interpreted byrunInterceptCont
, alltell
s (notsubmit
s) in application code won't get intercepted by our uses ofintercept
. You may or may not want that behaviour. If you don't want it, it's as simple as removingTell o
from the list of effectsReinterpretC
hides. - If any interpreter run after
editorializedToTell
uses theTell o
effect, then those uses oftell
won't get intercepted, even if we don't hide theTell o
effect. To prevent this happening, you typically want to follow up a use ofrunInterceptCont @eff
by immediately interpretingeff
.
Let's follow the advice from the last bullet point and combine our editorializedToTell
interpreter with an interpreter for Tell o
.
type EditorializedC o = CompositionC
'[ IntroUnderC (Editorialized o) '[Tell o]
, EditorializedToTellC o
, TellListC o
]
runEditorialized :: ( Carrier m
, Threaders '[SteppedThreads, ReaderThreads, WriterThreads] m p
)
=> EditorializedC o m a
-> m ([o], a)
runEditorialized =
runTellList
. editorializedToTell
. introUnder
. runComposition
This works, but it has a significant problem; that WriterThreads
threading constraint! runInterceptCont
makes use of the primitive effect Unravel
, and WriterThreads
doesn't accept it! This means although you can use runEditorialized
once, you can't use it multiple times; or combine it with any other interpreter that may use runInterceptCont
.
Because of this problem, the Control.Effect.Intercept
module actually offers alternative interpreters for State
and Tell
that can be used in place of the regular ones. These interpreters emit a SteppedThreads
threading constraint instead of the normal threading constraint of each corresponding interpreter, and SteppedThreads
does accept Unravels
, getting rid of the issue:
type EditorializedC o = CompositionC
'[ IntroUnderC (Editorialized o) '[Tell o]
, EditorializedToTellC o
, SteppedC (Tell o)
]
runEditorialized :: ( Carrier m
, Threaders '[SteppedThreads, ReaderThreads] m p
)
=> EditorializedC o m a
-> m ([o], a)
runEditorialized =
runTellListStepped
. editorializedToTell
. introUnder
. runComposition