CC-delcont-cxe-0.1.0.2: A monad transformers for multi-prompt delimited control

Control.Monad.CC.CCCxe

Contents

Description

This file is the CPS version of http://hackage.haskell.org/package/CC-delcont-exc's Control.Monad.CC.CCExc, implementing the identical interface

Monad transformer for multi-prompt delimited control It implements the superset of the interface described in

The first main difference is the use of generalized prompts, which do not have to be created with new_prompt and therefore can be defined at top level. That removes one of the main practical drawbacks of Dybvig et al implementations: the necessity to carry around the prompts throughout all the code.

The delimited continuation monad is parameterized by the flavor of generalized prompts. The end of this code defines several flavors; the library users may define their own. User-defined flavors are especially useful when user's code uses a small closed set of answer-types. Flavors PP and PD below are more general, assuming the set of possible answer-types is open and Typeable. If the user wishes to create several distinct prompts with the same answer-types, the user should use the flavor of prompts accepting an integral prompt identifier, such as PD. Prompts of the flavor PD correspond to the prompts in Dybvig, Peyton Jones, Sabry framework. If the user wishes to generate unique prompts, the user should arrange himself for the generation of unique integers (using a state monad, for example). On the other hand, the user can differentiate answer-types using `newtype.' The latter can only produce the set of distinct prompts that is fixed at run-time. Sometimes that is sufficient. There is not need to create a gensym monad then.

See Control.Monad.CC.CCExc for further comments about the implementation

Synopsis

Types

data CC p m a Source

Delimited-continuation monad transformer It is parameterized by the prompt flavor p The first argument is the regular (success) continuation, the second argument is the bubble, or a resumable exception

Instances

MonadTrans (CC p) 
Monad m => Monad (CC p m)

CC monad: general monadic operations

MonadIO m => MonadIO (CC p m) 

type SubCont p m a b = CC p m a -> CC p m bSource

The captured sub-continuation

type CCT p m a w = SubCont p m a w -> CC p m wSource

The type of control operator's body

type Prompt p m w = (forall x. CCT p m x w -> p m x, forall x. p m x -> Maybe (CCT p m x w))Source

Generalized prompts for the answer-type w: an injection-projection pair

Basic delimited control operations

pushPrompt :: Monad m => Prompt p m w -> CC p m w -> CC p m wSource

takeSubCont :: Monad m => Prompt p m w -> CCT p m x w -> CC p m xSource

Create the initial bubble

pushSubCont :: Monad m => SubCont p m a b -> CC p m a -> CC p m bSource

Apply the captured continuation

runCC :: Monad m => CC (p :: (* -> *) -> * -> *) m a -> m aSource

Useful derived operations

abortP :: Monad m => Prompt p m w -> CC p m w -> CC p m anySource

shiftP :: Monad m => Prompt p m w -> ((a -> CC p m w) -> CC p m w) -> CC p m aSource

shift0P :: Monad m => Prompt p m w -> ((a -> CC p m w) -> CC p m w) -> CC p m aSource

controlP :: Monad m => Prompt p m w -> ((a -> CC p m w) -> CC p m w) -> CC p m aSource

Pre-defined prompt flavors

data PS w m x Source

The extreme case: prompts for the single answer-type w. The monad (CC PS) then is the monad for regular (single-prompt) delimited continuations

ps :: Prompt (PS w) m wSource

data P2 w1 w2 m x Source

Prompts for the closed set of answer-types The following prompt flavor P2, for two answer-types w1 and w2, is given as an example. Typically, a programmer would define their own variant data type with variants for the answer-types that occur in their program.

p2L :: Prompt (P2 w1 w2) m w1Source

There are two generalized prompts of the flavor P2

p2R :: Prompt (P2 w1 w2) m w2Source

data PP m x Source

Prompts for the open set of answer-types

data PM c m x Source

The same as PP but with the phantom parameter c The parameter is useful to statically enforce various constrains (statically pass some information between shift and reset) The prompt PP is too dynamic: all errors are detected dynamically See Generator2.hs for an example

pm :: Typeable w => Prompt (PM c) m wSource

data PD m x Source

Open set of answer types, with an additional distinction (given by integer identifiers) This prompt flavor corresponds to the prompts in the Dybvig, Peyton-Jones, Sabry framework (modulo the Typeable constraint).

as_prompt_type :: Prompt p m w -> w -> Prompt p m wSource

It is often helpful, for clarity of error messages, to specify the answer-type associated with the prompt explicitly (rather than relying on the type inference to figure that out). The following function is useful for that purpose.