extensible-effects-2.6.3.0: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Lift

Description

Lifting primitive Monad types to effectful computations. We only allow a single Lifted Monad because Monads aren't commutative (e.g. Maybe (IO a) is functionally distinct from IO (Maybe a)).

Synopsis

Documentation

newtype Lift m a Source #

Lifting: emulating monad transformers

Constructors

Lift (m a) 

Instances

MonadBase m m => MonadBaseControl m (Eff ((:) (* -> *) (Lift * m) ([] (* -> *)))) Source # 

Associated Types

type StM (Eff (((* -> *) ': Lift * m) [* -> *]) :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Eff (((* -> *) ': Lift * m) [* -> *])) m -> m a) -> Eff (((* -> *) ': Lift * m) [* -> *]) a #

restoreM :: StM (Eff (((* -> *) ': Lift * m) [* -> *])) a -> Eff (((* -> *) ': Lift * m) [* -> *]) a #

type StM (Eff ((:) (* -> *) (Lift * m) ([] (* -> *)))) a Source # 
type StM (Eff ((:) (* -> *) (Lift * m) ([] (* -> *)))) a = a

type Lifted m r = SetMember Lift (Lift m) r Source #

A convenient alias to 'SetMember Lift (Lift m) r'

type LiftedBase m r = (SetMember Lift (Lift m) r, MonadBaseControl m (Eff r)) Source #

Same as Lifted but with additional MonadBaseControl constraint

lift :: SetMember Lift (Lift m) r => m a -> Eff r a Source #

We make the Lift layer to be unique, using SetMember

runLift :: Monad m => Eff '[Lift m] w -> m w Source #

The handler of Lift requests. It is meant to be terminal: we only allow a single Lifted Monad.

catchDynE :: forall e a r. (Lifted IO r, Exception e) => Eff r a -> (e -> Eff r a) -> Eff r a Source #

Catching of dynamic exceptions See the problem in http://okmij.org/ftp/Haskell/misc.html#catch-MonadIO