| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Effect.Internal
Synopsis
- class Monad m => Carrier m where
- type Eff e m = Effs '[e] m
- type Effs es m = (EffMembers es (Derivs m), Carrier m)
- send :: (Member e (Derivs m), Carrier m) => e m a -> m a
- type Threaders cs m p = (p ~ Prims m, SatisfiesAll p cs)
- type family SatisfiesAll (q :: k) cs :: Constraint where ...
- type RunC = Identity
- run :: RunC a -> a
- newtype SubsumeC (e :: Effect) m a = SubsumeC {- unSubsumeC :: m a
 
- subsume :: (Carrier m, Member e (Derivs m)) => SubsumeC e m a -> m a
Documentation
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.
Minimal complete definition
Associated Types
type Derivs m :: [Effect] Source #
The derived effects that m carries. Each derived effect is eventually
 reformulated into terms of the primitive effects Prims mDerivs m
In application code, you gain access to effects by placing membership
 constraints upon Derivs mEff or Effs for this
 purpose.
Although rarely relevant for users, Derivs mlift. Such effects don't
 need to be part of Prims m
For example, first order effects such as State
 never need to be part of 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 Prims mDerivs m
However, running interpreters may place other kinds of constraints upon
 Prims mThreaders.
 If you want to run such an effect interpreter inside application code, you
 have to propagate such threading constraints through your application.
Prims mlift. Any other effects can be placed in Derivs m
Methods
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 =reformulateidalgPrims
which serves as the default implementation.
Instances
type Eff e m = Effs '[e] m Source #
(Morally) a type synonym for
 (.
 This and Member e (Derivs m), Carrier m)Effs are the typical methods to gain
 access to effects.
Unlike Member, Eff gives Bundle special treatment.
 As a side-effect, Eff will get stuck if e is a type variable.
If you need access to some completely polymorphic effect e,
 use ( instead of Member e (Derivs m), Carrier m)Eff e m.
type Effs es m = (EffMembers es (Derivs m), Carrier m) Source #
A variant of Eff that takes a list of effects, and expands them into
 multiple Member constraints on Derivs mEff are the typical methods to gain access to effects.
Like Eff, Effs gives Bundle special treatment.
 As a side-effect, Effs will get stuck if any element of the list
 is a type variable.
If you need access to some completetely polymorphic effect e,
 use a separate Member e (Derivs m)
send :: (Member e (Derivs m), Carrier m) => e m a -> m a Source #
Perform an action of an effect.
send should be used to create actions of your own effects.
 For example:
data CheckString :: Effect where CheckString :: String -> CheckString m Bool checkString :: Eff CheckString m => String -> m Bool checkString str = send (CheckString str)
type Threaders cs m p = (p ~ Prims m, SatisfiesAll p cs) Source #
A constraint that Prims mcs.
This is used for threading constraints.
Every interpreter that relies on an underlying
 non-trivial monad transformer -- such as runState,
 which uses StateT internally --
 must be able to lift all primitive effect handlers of the monad it's transforming
 so that the resulting transformed monad can also handle the primitive effects.
The ability of a monad transformer to lift handlers of a particular primitive effect is called threading that effect. Threading constraints correspond to the requirement that the primitive effects of the monad that's being transformed can be thread by certain monad transformers.
For example, the runState places the threading
 constraint StateThreads on Prims mStateC s mm does.
Threaders is used to handle threading constraints.
 Threaders '[StateThreads, ExceptThreads] m prunState and
 runError with the carrier m.
Sometimes, you may want to have a local effect which you interpret
 inside of application code, such as a local State
 or Error effect. In such cases, try to use
 split interpretation instead of using interpreters with threading constraints
 inside of application code. If you can't, then using Threaders
 is necessary to propagate the threading constraints
 throughout the application.
The third argument p should always be a polymorphic type variable, which
 you can simply provide and ignore.
 It exists as a work-around to the fact that many threading constraints
 don't actually work if they operate on Prims mPrims.
So Threaders '[StateThreads] m pStateThreads (Prims m)(p ~ Prims m, StateThreads p)
type family SatisfiesAll (q :: k) cs :: Constraint where ... Source #
Equations
| SatisfiesAll q '[] = () | |
| SatisfiesAll q (c ': cs) = (c q, SatisfiesAll q cs) | 
Extract the final result from a computation of which no effects remain to be handled.
newtype SubsumeC (e :: Effect) m a Source #
Constructors
| SubsumeC | |
| Fields 
 | |
Instances
subsume :: (Carrier m, Member e (Derivs m)) => SubsumeC e m a -> m a Source #
Interpret an effect in terms of another, identical effect.
This is very rarely useful, but one use-case is to transform reinterpreters into regular interpreters.
For example,
 subsume . reinterpretSimple @e hinterpretSimple @e h