Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype BaseControl b m a where
- GainBaseControl :: (forall z. (MonadBaseControl b z, Coercible z m) => Proxy# z -> a) -> BaseControl b m a
- threadBaseControlViaClass :: forall b t m a. (MonadTrans t, Monad m, forall z. MonadBaseControl b z => MonadBaseControl b (t z), forall z. Coercible z m => Coercible (t z) (t m)) => (forall x. BaseControl b m x -> m x) -> BaseControl b (t m) a -> t m a
- threadOptionalViaBaseControl :: forall s t m a. (Functor s, Monad m, Monad (t m), ThreadsEff t (BaseControl m)) => (forall x. Optional s m x -> m x) -> Optional s (t m) a -> t m a
- newtype WriterCPS s m a = WriterCPS {
- unWriterCPS :: WriterT s m a
Documentation
newtype BaseControl b m a where Source #
A helper primitive effect that allows for lowering computations 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
.
BaseControl
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 (BaseControl
b)threadBaseControlViaClass
can help you with that.
The following threading constraints accept BaseControl
:
GainBaseControl :: (forall z. (MonadBaseControl b z, Coercible z m) => Proxy# z -> a) -> BaseControl b m a |
Instances
threadBaseControlViaClass :: forall b t m a. (MonadTrans t, Monad m, forall z. MonadBaseControl b z => MonadBaseControl b (t z), forall z. Coercible z m => Coercible (t z) (t m)) => (forall x. BaseControl b m x -> m x) -> BaseControl b (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance, given that ThreadsEff
t (BaseControl
b)t
lifts
for any MonadBaseControl
bb
.
threadOptionalViaBaseControl :: forall s t m a. (Functor s, Monad m, Monad (t m), ThreadsEff t (BaseControl m)) => (forall x. Optional s m x -> m x) -> Optional s (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance, given that ThreadsEff
t (Optional
s)t
threads
for any BaseControl
bb
.
newtype WriterCPS s m a Source #
WriterCPS | |
|
Instances
MonadBase b m => MonadBase b (WriterCPS s m) Source # | |
Defined in Control.Effect.Type.Internal.BaseControl | |
(Monoid s, MonadBaseControl b m) => MonadBaseControl b (WriterCPS s m) Source # | |
MonadTrans (WriterCPS s) Source # | |
Defined in Control.Effect.Type.Internal.BaseControl | |
Monad m => Monad (WriterCPS s m) Source # | |
Functor m => Functor (WriterCPS s m) Source # | |
Monad m => Applicative (WriterCPS s m) Source # | |
Defined in Control.Effect.Type.Internal.BaseControl pure :: a -> WriterCPS s m a # (<*>) :: WriterCPS s m (a -> b) -> WriterCPS s m a -> WriterCPS s m b # liftA2 :: (a -> b -> c) -> WriterCPS s m a -> WriterCPS s m b -> WriterCPS s m c # (*>) :: WriterCPS s m a -> WriterCPS s m b -> WriterCPS s m b # (<*) :: WriterCPS s m a -> WriterCPS s m b -> WriterCPS s m a # | |
type StM (WriterCPS s m) a Source # | |
Defined in Control.Effect.Type.Internal.BaseControl |