| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.Lift.Local
Description
Lifting the local operation.
- class MonadTrans t => LiftLocal t where
- type Local r m a = (r -> r) -> m a -> m a
- defaultLiftLocal :: (Monad m, LiftLocal n) => (forall x. n m x -> t m x) -> (forall o x. t o x -> n o x) -> m r -> (forall a. Local r m a) -> forall a. Local r (t m) a
- module Control.Monad.Trans.Class
Documentation
class MonadTrans t => LiftLocal t where Source #
The class of monad transformers capable of lifting local.
Minimal complete definition
Methods
liftLocal :: Monad m => m r -> (forall a. Local r m a) -> forall a. Local r (t m) a Source #
Lift the local operation.
Instances
| LiftLocal MaybeT Source # | |
| LiftLocal ListT Source # | |
| Monoid w => LiftLocal (WriterT w) Source # | |
| Monoid w => LiftLocal (WriterT w) Source # | |
| LiftLocal (StateT s) Source # | |
| LiftLocal (StateT s) Source # | |
| LiftLocal (IdentityT *) Source # | |
| LiftLocal (ExceptT e) Source # | |
| Monoid w => LiftLocal (WriterT w) Source # | |
| LiftLocal (ReaderT * r) Source # | |
| LiftLocal (ContT * r) Source # | |
| Monoid w => LiftLocal (RWST r w s) Source # | |
| Monoid w => LiftLocal (RWST r w s) Source # | |
| Monoid w => LiftLocal (RWST r w s) Source # | |
type Local r m a = (r -> r) -> m a -> m a Source #
Signature of the local operation,
introduced in Control.Monad.Trans.Reader.
Arguments
| :: (Monad m, LiftLocal n) | |
| => (forall x. n m x -> t m x) | Monad constructor |
| -> (forall o x. t o x -> n o x) | Monad deconstructor |
| -> m r | |
| -> (forall a. Local r m a) | |
| -> forall a. Local r (t m) a |
Default definition for the liftLocal method.
module Control.Monad.Trans.Class