| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | R.Paterson@city.ac.uk | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
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
- type Cont r = ContT r Identity
- cont :: ((a -> r) -> r) -> Cont r a
- runCont :: Cont r a -> (a -> r) -> r
- evalCont :: Cont r r -> r
- mapCont :: (r -> r) -> Cont r a -> Cont r a
- withCont :: ((b -> r) -> a -> r) -> Cont r a -> Cont r b
- reset :: Cont r r -> Cont r' r
- shift :: ((a -> r) -> Cont r r) -> Cont r a
- newtype ContT r m a = ContT {- runContT :: (a -> m r) -> m r
 
- evalContT :: Monad m => ContT r m r -> m r
- mapContT :: (m r -> m r) -> ContT r m a -> ContT r m a
- withContT :: ((b -> m r) -> a -> m r) -> ContT r m a -> ContT r m b
- callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a
- resetT :: Monad m => ContT r m r -> ContT r' m r
- shiftT :: Monad m => ((a -> m r) -> ContT r m r) -> ContT r m a
- liftLocal :: Monad m => m r' -> ((r' -> r') -> m r -> m r) -> (r' -> r') -> ContT r m a -> ContT r m a
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)
Arguments
| :: Cont r a | continuation computation ( | 
| -> (a -> r) | the final continuation, which produces
 the final result (often  | 
| -> r | 
The result of running a CPS computation with a given final continuation.
 (The inverse of cont)
Delimited continuations
The ContT monad transformer
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.
Instances
| MonadTrans (ContT r) Source # | |
| MonadFail m => MonadFail (ContT r m) Source # | |
| Defined in Control.Monad.Trans.Cont | |
| MonadIO m => MonadIO (ContT r m) Source # | |
| Defined in Control.Monad.Trans.Cont | |
| Applicative (ContT r m) Source # | |
| Defined in Control.Monad.Trans.Cont | |
| Functor (ContT r m) Source # | |
| Monad (ContT r m) Source # | |
| Generic (ContT r m a) Source # | |
| type Rep (ContT r m a) Source # | |
| Defined in Control.Monad.Trans.Cont | |
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.