transformers-0.6.0.2: Concrete functor and monad transformers
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Cont

Description

Continuation monads.

Delimited continuation operators are taken from Kenichi Asai and Oleg Kiselyov's tutorial at CW 2011, "Introduction to programming with shift and reset" (http://okmij.org/ftp/continuations/#tutorial).

Synopsis

The Cont monad

type Cont r = ContT r Identity Source #

Continuation monad. Cont r a is a CPS ("continuation-passing style") computation that produces an intermediate result of type a within a CPS computation whose final result type is r.

The return function simply creates a continuation which passes the value on.

The >>= operator adds the bound function into the continuation chain.

cont :: ((a -> r) -> r) -> Cont r a Source #

Construct a continuation-passing computation from a function. (The inverse of runCont)

runCont Source #

Arguments

:: Cont r a

continuation computation (Cont).

-> (a -> r)

the final continuation, which produces the final result (often id).

-> r 

The result of running a CPS computation with a given final continuation. (The inverse of cont)

evalCont :: Cont r r -> r Source #

The result of running a CPS computation with the identity as the final continuation.

mapCont :: (r -> r) -> Cont r a -> Cont r a Source #

Apply a function to transform the result of a continuation-passing computation.

withCont :: ((b -> r) -> a -> r) -> Cont r a -> Cont r b Source #

Apply a function to transform the continuation passed to a CPS computation.

Delimited continuations

reset :: Cont r r -> Cont r' r Source #

reset m delimits the continuation of any shift inside m.

shift :: ((a -> r) -> Cont r r) -> Cont r a Source #

shift f captures the continuation up to the nearest enclosing reset and passes it to f:

The ContT monad transformer

newtype ContT r m a Source #

The continuation monad transformer. Can be used to add continuation handling to any type constructor: the Monad instance and most of the operations do not require m to be a monad.

ContT is not a functor on the category of monads, and many operations cannot be lifted through it.

Constructors

ContT 

Fields

Instances

Instances details
MonadTrans (ContT r) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a Source #

Monad (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

(>>=) :: ContT r m a -> (a -> ContT r m b) -> ContT r m b #

(>>) :: ContT r m a -> ContT r m b -> ContT r m b #

return :: a -> ContT r m a #

Functor (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

fmap :: (a -> b) -> ContT r m a -> ContT r m b #

(<$) :: a -> ContT r m b -> ContT r m a #

MonadFail m => MonadFail (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

fail :: String -> ContT r m a #

Applicative (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

pure :: a -> ContT r m a #

(<*>) :: ContT r m (a -> b) -> ContT r m a -> ContT r m b #

liftA2 :: (a -> b -> c) -> ContT r m a -> ContT r m b -> ContT r m c #

(*>) :: ContT r m a -> ContT r m b -> ContT r m b #

(<*) :: ContT r m a -> ContT r m b -> ContT r m a #

MonadIO m => MonadIO (ContT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

Generic (ContT r m a) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

Associated Types

type Rep (ContT r m a) :: Type -> Type #

Methods

from :: ContT r m a -> Rep (ContT r m a) x #

to :: Rep (ContT r m a) x -> ContT r m a #

type Rep (ContT r m a) Source # 
Instance details

Defined in Control.Monad.Trans.Cont

type Rep (ContT r m a) = D1 ('MetaData "ContT" "Control.Monad.Trans.Cont" "transformers-0.6.0.2-3vZqekptSPoIT7uEdKk0Uz" 'True) (C1 ('MetaCons "ContT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runContT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((a -> m r) -> m r))))

evalContT :: Monad m => ContT r m r -> m r Source #

The result of running a CPS computation with return as the final continuation.

mapContT :: (m r -> m r) -> ContT r m a -> ContT r m a Source #

Apply a function to transform the result of a continuation-passing computation. This has a more restricted type than the map operations for other monad transformers, because ContT does not define a functor in the category of monads.

withContT :: ((b -> m r) -> a -> m r) -> ContT r m a -> ContT r m b Source #

Apply a function to transform the continuation passed to a CPS computation.

callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a Source #

callCC (call-with-current-continuation) calls its argument function, passing it the current continuation. It provides an escape continuation mechanism for use with continuation monads. Escape continuations one allow to abort the current computation and return a value immediately. They achieve a similar effect to throwE and catchE within an ExceptT monad. The advantage of this function over calling return is that it makes the continuation explicit, allowing more flexibility and better control.

The standard idiom used with callCC is to provide a lambda-expression to name the continuation. Then calling the named continuation anywhere within its scope will escape from the computation, even if it is many layers deep within nested computations.

Delimited continuations

resetT :: Monad m => ContT r m r -> ContT r' m r Source #

resetT m delimits the continuation of any shiftT inside m.

shiftT :: Monad m => ((a -> m r) -> ContT r m r) -> ContT r m a Source #

shiftT f captures the continuation up to the nearest enclosing resetT and passes it to f:

Lifting other operations

liftLocal :: Monad m => m r' -> ((r' -> r') -> m r -> m r) -> (r' -> r') -> ContT r m a -> ContT r m a Source #

liftLocal ask local yields a local function for ContT r m.