Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Lifting the callCC
operation.
- class MonadTrans t => LiftCallCC t where
- type CallCC m a b = ((a -> m b) -> m a) -> m a
- defaultLiftCallCC :: (Monad m, LiftCallCC n) => (forall x. n m x -> t m x) -> (forall o x. t o x -> n o x) -> CallCC m (StT n a) (StT n b) -> CallCC (t m) a b
- defaultLiftCallCC' :: (Monad m, LiftCallCC n) => (forall x. n m x -> t m x) -> (forall o x. t o x -> n o x) -> CallCC m (StT n a) (StT n b) -> CallCC (t m) a b
- module Control.Monad.Trans.Class
Documentation
class MonadTrans t => LiftCallCC t where Source #
The class of monad transformers capable of lifting callCC
.
liftCallCC :: Monad m => CallCC m (StT t a) (StT t b) -> CallCC (t m) a b Source #
Lift the callCC
operation.
Should satisfy the uniformity property
lift
(f k) = f' (lift
. k) =>lift
(cf f) =liftCallCC
cf f'
liftCallCC' :: Monad m => CallCC m (StT t a) (StT t b) -> CallCC (t m) a b Source #
Lift the callCC
operation.
This is an alternative version of liftCallCC
included for historical
reasons. It has a different lifting behavior for the StateT
and RWST
monad transformers. Matches what mtl
does but doesn't satisfy the
uniformity property.
LiftCallCC MaybeT Source # | |
LiftCallCC ListT Source # | |
Monoid w => LiftCallCC (WriterT w) Source # | |
Monoid w => LiftCallCC (WriterT w) Source # | |
LiftCallCC (StateT s) Source # | |
LiftCallCC (StateT s) Source # | |
LiftCallCC (IdentityT *) Source # | |
LiftCallCC (ExceptT e) Source # | |
Monoid w => LiftCallCC (WriterT w) Source # | |
LiftCallCC (ReaderT * r) Source # | |
Monoid w => LiftCallCC (RWST r w s) Source # | |
Monoid w => LiftCallCC (RWST r w s) Source # | |
Monoid w => LiftCallCC (RWST r w s) Source # | |
type CallCC m a b = ((a -> m b) -> m a) -> m a #
Signature of the callCC
operation,
introduced in Control.Monad.Trans.Cont.
Any lifting function liftCallCC
should satisfy
lift
(f k) = f' (lift
. k) =>lift
(cf f) = liftCallCC cf f'
:: (Monad m, LiftCallCC n) | |
=> (forall x. n m x -> t m x) | Monad constructor |
-> (forall o x. t o x -> n o x) | Monad deconstructor |
-> CallCC m (StT n a) (StT n b) | |
-> CallCC (t m) a b |
Default definition for the liftCallCC
method.
:: (Monad m, LiftCallCC n) | |
=> (forall x. n m x -> t m x) | Monad constructor |
-> (forall o x. t o x -> n o x) | Monad deconstructor |
-> CallCC m (StT n a) (StT n b) | |
-> CallCC (t m) a b |
Default definition for the liftCallCC'
method.
module Control.Monad.Trans.Class