transformers-lift-0.2.0.2: Ad-hoc type classes for lifting

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Lift.Listen

Description

Lifting the listen operation.

Synopsis

Documentation

class MonadTrans t => LiftListen t where Source #

The class of monad transformers capable of lifting listen.

Methods

liftListen :: Monad m => Listen w m (StT t a) -> Listen w (t m) a Source #

Lift the listen operation. Should satisfy the uniformity property

Instances
LiftListen MaybeT Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT MaybeT a) -> Listen w (MaybeT m) a Source #

Monoid w' => LiftListen (WriterT w') Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (WriterT w') a) -> Listen w (WriterT w' m) a Source #

Monoid w' => LiftListen (AccumT w') Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (AccumT w') a) -> Listen w (AccumT w' m) a Source #

Monoid w' => LiftListen (WriterT w') Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (WriterT w') a) -> Listen w (WriterT w' m) a Source #

LiftListen (StateT s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (StateT s) a) -> Listen w (StateT s m) a Source #

LiftListen (StateT s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (StateT s) a) -> Listen w (StateT s m) a Source #

LiftListen (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT IdentityT a) -> Listen w (IdentityT m) a Source #

LiftListen (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (ExceptT e) a) -> Listen w (ExceptT e m) a Source #

Monoid w' => LiftListen (WriterT w') Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (WriterT w') a) -> Listen w (WriterT w' m) a Source #

LiftListen (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (ReaderT r) a) -> Listen w (ReaderT r m) a Source #

Monoid w' => LiftListen (RWST r w' s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (RWST r w' s) a) -> Listen w (RWST r w' s m) a Source #

Monoid w' => LiftListen (RWST r w' s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (RWST r w' s) a) -> Listen w (RWST r w' s m) a Source #

Monoid w' => LiftListen (RWST r w' s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Listen

Methods

liftListen :: Monad m => Listen w m (StT (RWST r w' s) a) -> Listen w (RWST r w' s m) a Source #

type Listen w (m :: Type -> Type) a = m a -> m (a, w) #

Signature of the listen operation, introduced in Control.Monad.Trans.Writer. Any lifting function liftListen should satisfy

  • lift . liftListen = liftListen . lift

defaultLiftListen Source #

Arguments

:: (Monad m, LiftListen n) 
=> (forall x. n m x -> t m x)

Monad constructor

-> (forall o x. t o x -> n o x)

Monad deconstructor

-> Listen w m (StT n a) 
-> Listen w (t m) a 

Default definition for the liftListen method.