in-other-words-0.2.1.1: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Type.Unlift

Contents

Synopsis

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 ThreadsEff t (Unlift b) instance (if possible). threadUnliftViaClass can help you with that.

The following threading constraints accept Unlift:

Constructors

Unlift :: forall b m a. ((forall x. m x -> b x) -> b a) -> Unlift b m a 

Instances

Instances details
Carrier m => PrimHandler UnliftH (Unlift m) m Source # 
Instance details

Defined in Control.Effect.Internal.Unlift

ThreadsEff (ReaderT i) (Unlift b) Source # 
Instance details

Defined in Control.Effect.Type.Unlift

Methods

threadEff :: Monad m => (forall x. Unlift b m x -> m x) -> Unlift b (ReaderT i m) a -> ReaderT i m a 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 ThreadsEff (Unlift b) t instance, given that t is a MonadTransControl where StT t a ~ a holds for all a.

threadBaseControlViaUnlift :: forall b t m a. (Monad m, MonadTrans t, forall z. Monad z => Monad (t z), forall z. Coercible z m => Coercible (t z) (t m), forall z. Monad z => ThreadsEff t (Unlift z)) => (forall x. BaseControl b m x -> m x) -> BaseControl b (t m) a -> t m a Source #

A valid definition of threadEff for a ThreadsEff (BaseControl b) t instance, given that t threads Unlift z for any Monad z.

class (MonadBaseControl b m, forall x. Pure m x) => MonadBaseControlPure b m Source #

A constraint synonym for MonadBaseControl b m together with that StM m a ~ a for all a.

Instances

Instances details
(MonadBaseControl b m, forall x. Pure m x) => MonadBaseControlPure b m Source # 
Instance details

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

Instances details
(MonadTransControl t, forall x. PureT t x) => MonadTransControlPure t Source # 
Instance details

Defined in Control.Effect.Type.Unlift

unliftT :: forall t m a. (MonadTransControlPure t, Monad m) => ((forall n x. Monad n => t n x -> n x) -> m a) -> t m a Source #