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

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Lift.CallCC

Description

Lifting the callCC operation.

Synopsis

Documentation

class MonadTrans t => LiftCallCC t where Source #

The class of monad transformers capable of lifting callCC.

Minimal complete definition

liftCallCC

Methods

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

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.

Instances

LiftCallCC MaybeT Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT MaybeT a) (StT MaybeT b) -> CallCC (MaybeT m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT MaybeT a) (StT MaybeT b) -> CallCC (MaybeT m) a b Source #

LiftCallCC ListT Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT ListT a) (StT ListT b) -> CallCC (ListT m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT ListT a) (StT ListT b) -> CallCC (ListT m) a b Source #

Monoid w => LiftCallCC (WriterT w) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

Monoid w => LiftCallCC (WriterT w) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

LiftCallCC (StateT s) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (StateT s) a) (StT (StateT s) b) -> CallCC (StateT s m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (StateT s) a) (StT (StateT s) b) -> CallCC (StateT s m) a b Source #

LiftCallCC (StateT s) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (StateT s) a) (StT (StateT s) b) -> CallCC (StateT s m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (StateT s) a) (StT (StateT s) b) -> CallCC (StateT s m) a b Source #

LiftCallCC (IdentityT *) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (IdentityT *) a) (StT (IdentityT *) b) -> CallCC (IdentityT * m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (IdentityT *) a) (StT (IdentityT *) b) -> CallCC (IdentityT * m) a b Source #

LiftCallCC (ExceptT e) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (ExceptT e) a) (StT (ExceptT e) b) -> CallCC (ExceptT e m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (ExceptT e) a) (StT (ExceptT e) b) -> CallCC (ExceptT e m) a b Source #

Monoid w => LiftCallCC (WriterT w) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (WriterT w) a) (StT (WriterT w) b) -> CallCC (WriterT w m) a b Source #

LiftCallCC (ReaderT * r) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (ReaderT * r) a) (StT (ReaderT * r) b) -> CallCC (ReaderT * r m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (ReaderT * r) a) (StT (ReaderT * r) b) -> CallCC (ReaderT * r m) a b Source #

Monoid w => LiftCallCC (RWST r w s) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b Source #

Monoid w => LiftCallCC (RWST r w s) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b Source #

Monoid w => LiftCallCC (RWST r w s) Source # 

Methods

liftCallCC :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b Source #

liftCallCC' :: Monad m => CallCC m (StT (RWST r w s) a) (StT (RWST r w s) b) -> CallCC (RWST r w s m) a b 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'

defaultLiftCallCC Source #

Arguments

:: (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.

defaultLiftCallCC' Source #

Arguments

:: (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.