Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Regional s :: Effect where
- Regionally :: s -> m a -> Regional s m a
- type Hoist (b :: * -> *) = Regional (HoistCall b)
- regionally :: Eff (Regional s) m => s -> m a -> m a
- hoist :: Eff (Hoist b) m => (forall x. b x -> b x) -> m a -> m a
- runHoist :: Carrier m => HoistC m a -> m a
- hoistToFinal :: (MonadBaseControl b m, Carrier m) => HoistToFinalC b m a -> m a
- threadRegionalViaOptional :: (ThreadsEff t (Optional (Const s)), Monad m) => (forall x. Regional s m x -> m x) -> Regional s (t m) a -> t m a
- powerAlgHoist :: forall m p a. Algebra' p m a -> Algebra' (Hoist m ': p) m a
- powerAlgHoistFinal :: forall b m p a. MonadBaseControl b m => Algebra' p m a -> Algebra' (Hoist b ': p) m a
- data HoistC m a
- type HoistToFinalC b = InterpretPrimC HoistToFinalH (Hoist b)
Effects
data Regional s :: Effect where Source #
A helper primitive effect for manipulating a region.
Helper primitive effects are effects that allow you to avoid interpreting one
of your own effects as a primitive if the power needed from direct access to
the underlying monad can instead be provided by the relevant helper primitive
effect. The reason why you'd want to do this is that helper primitive effects
already have ThreadsEff
instances defined for them; so you don't have to
define any for your own effect.
The helper primitive effects offered in this library are -- in order of
ascending power -- Regional
,
Optional
, BaseControl
and Unlift
.
The typical use-case of Regional
is to lift a natural transformation
of a base monad.
Hoist
and accompaning interpreters is
provided as a specialization of Regional
for this purpose.
Regional
in its most general form lacks a pre-defined interpreter:
when not using Hoist
, you're expected to define
your own interpreter for Regional
(treating it as a primitive effect).
Regional
is typically used as a primitive effect.
If you define a Carrier
that relies on a novel
non-trivial monad transformer t
, then you need to make a
a
instance (if possible).
ThreadsEff
t (Regional
s)threadRegionalViaOptional
can help you with that.
The following threading constraints accept Regional
:
Regionally :: s -> m a -> Regional s m a |
Instances
ThreadsEff ListT (Regional s) Source # | |
(Carrier m, MonadBaseControl b m) => PrimHandler HoistToFinalH (Hoist b) m Source # | |
Defined in Control.Effect.Internal.Regional effPrimHandler :: EffPrimHandler (Hoist b) m Source # | |
Carrier m => PrimHandler HoistH (Hoist m) m Source # | |
Defined in Control.Effect.Internal.Regional effPrimHandler :: EffPrimHandler (Hoist m) m Source # | |
ThreadsEff (ExceptT e) (Regional s) Source # | |
ThreadsEff (WriterT w) (Regional s) Source # | |
ThreadsEff (StateT i) (Regional s) Source # | |
ThreadsEff (ReaderT i) (Regional s) Source # | |
ThreadsEff (StateT i) (Regional s) Source # | |
ThreadsEff (WriterT w) (Regional s) Source # | |
Monoid w => ThreadsEff (WriterT w) (Regional s) Source # | |
ThreadsEff (FreeT f) (Regional s) Source # | |
Actions
regionally :: Eff (Regional s) m => s -> m a -> m a Source #
Execute a computation modified in some way, providing
the interpreter of
a constant to indicate
how the computation should be modified.Regional
s
hoist :: Eff (Hoist b) m => (forall x. b x -> b x) -> m a -> m a Source #
Lift a natural transformation of a base monad to the current monad.
Interpretations
hoistToFinal :: (MonadBaseControl b m, Carrier m) => HoistToFinalC b m a -> m a Source #
Run a
effect, where the base monad Hoist
bb
is the final base monad.
Derivs
(HoistToFinalC
b m) =Hoist
b ':Derivs
m
Prims
(HoistToFinalC
b m) =Hoist
b ':Prims
m
Threading utilities
threadRegionalViaOptional :: (ThreadsEff t (Optional (Const s)), Monad m) => (forall x. Regional s m x -> m x) -> Regional s (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance,
given that ThreadsEff
(Regional
s) tt
threads
for any functor Optional
ff
.
Combinators for Algebra
s
powerAlgHoistFinal :: forall b m p a. MonadBaseControl b m => Algebra' p m a -> Algebra' (Hoist b ': p) m a Source #
Carriers
Instances
type HoistToFinalC b = InterpretPrimC HoistToFinalH (Hoist b) Source #