| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.Lift.Listen
Description
Lifting the listen operation.
- class MonadTrans t => LiftListen t where
- type Listen w m a = m a -> m (a, w)
- defaultLiftListen :: (Monad m, LiftListen n) => (forall x. n m x -> t m x) -> (forall o x. t o x -> n o x) -> Listen w m (StT n a) -> Listen w (t m) a
- module Control.Monad.Trans.Class
Documentation
class MonadTrans t => LiftListen t where Source #
The class of monad transformers capable of lifting listen.
Minimal complete definition
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
lift.liftListen=liftListen.lift
Instances
| LiftListen MaybeT Source # | |
| Monoid w' => LiftListen (WriterT w') Source # | |
| Monoid w' => LiftListen (WriterT w') Source # | |
| LiftListen (StateT s) Source # | |
| LiftListen (StateT s) Source # | |
| LiftListen (IdentityT *) Source # | |
| LiftListen (ExceptT e) Source # | |
| Monoid w' => LiftListen (WriterT w') Source # | |
| LiftListen (ReaderT * r) Source # | |
| Monoid w' => LiftListen (RWST r w' s) Source # | |
| Monoid w' => LiftListen (RWST r w' s) Source # | |
| Monoid w' => LiftListen (RWST r w' s) Source # | |
type Listen w m 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
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.
module Control.Monad.Trans.Class