Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Unlift b :: Effect where
- threadUnliftViaClass :: forall b t m a. (MonadTransControlPure t, Monad m) => (forall x. Unlift b m x -> m x) -> Unlift b (t m) a -> t m a
- class (MonadBaseControl b m, forall x. Pure m x) => MonadBaseControlPure b m
- unliftBase :: forall b m a. MonadBaseControlPure b m => ((forall x. m x -> b x) -> b a) -> m a
- class (MonadTransControl t, forall x. PureT t x) => MonadTransControlPure t
- unliftT :: forall t m a. (MonadTransControlPure t, Monad m) => ((forall n x. Monad n => t n x -> n x) -> m a) -> t m a
Effects
newtype Unlift b :: Effect where Source #
A helper primitive effect for unlifting to a base monad.
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
.
Unlift
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
instance (if possible).
ThreadsEff
t (Unlift
b)threadUnliftViaClass
can help you with that.
The following threading constraints accept Unlift
:
Instances
Carrier m => PrimHandler UnliftH (Unlift m) m Source # | |
Defined in Control.Effect.Internal.Unlift effPrimHandler :: EffPrimHandler (Unlift m) m Source # | |
ThreadsEff (ReaderT i) (Unlift b) Source # | |
threadUnliftViaClass :: forall b t m a. (MonadTransControlPure t, Monad m) => (forall x. Unlift b m x -> m x) -> Unlift b (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance,
given that ThreadsEff
(Unlift
b) tt
is a MonadTransControl
where
holds for all StT
t a ~ aa
.
class (MonadBaseControl b m, forall x. Pure m x) => MonadBaseControlPure b m Source #
A constraint synonym for
together
with that MonadBaseControl
b mStM m a ~ a
for all a
.
Instances
(MonadBaseControl b m, forall x. Pure m x) => MonadBaseControlPure b m Source # | |
Defined in Control.Effect.Type.Unlift |
unliftBase :: forall b m a. MonadBaseControlPure b m => ((forall x. m x -> b x) -> b a) -> m a Source #
class (MonadTransControl t, forall x. PureT t x) => MonadTransControlPure t Source #
Instances
(MonadTransControl t, forall x. PureT t x) => MonadTransControlPure t Source # | |
Defined in Control.Effect.Type.Unlift |