-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Delimited continuations and dynamically scoped variables -- -- An implementation of multi-prompt delimited continuations based on the -- paper, A Monadic Framework for Delimited Continuations, by R. -- Kent Dybvig, Simon Peyton Jones and Amr Sabry -- (http://www.cs.indiana.edu/~sabry/papers/monadicDC.pdf). It -- also includes a corresponding implementation of dynamically scoped -- variables, as implemented in the paper, Delimited Dynamic -- Binding, by Oleg Kiselyov, Chung-chieh Shan and Amr Sabry -- (http://okmij.org/ftp/papers/DDBinding.pdf), adapted from the -- original haskell code, -- (http://okmij.org/ftp/packages/DBplusDC.tar.gz). @package CC-delcont @version 0.2.1.0 -- | A monadic treatment of delimited continuations. -- -- Adapted from the paper A Monadic Framework for Delimited -- Continuations, by R. Kent Dybvig, Simon Peyton Jones and Amr Sabry -- (http://www.cs.indiana.edu/~sabry/papers/monadicDC.pdf) -- -- This module implements the generation of unique prompt names to be -- used as delimiters. module Control.Monad.CC.Prompt -- | The prompt generation monad. Represents the type of computations that -- make use of a supply of unique prompts. data P ans m a -- | The prompt type, parameterized by two types: * ans : The region -- identifier, used to ensure that prompts are only used within the same -- context in which they are created. -- -- data Prompt ans a -- | Runs a computation that makes use of prompts, yielding a result in the -- underlying monad. runP :: (Monad m) => P ans m ans -> m ans -- | Generates a new, unique prompt newPromptName :: (Monad m) => P ans m (Prompt ans a) -- | Tests to determine if two prompts are equal. If so, it provides -- evidence of that fact, in the form of an Equal. eqPrompt :: Prompt ans a -> Prompt ans b -> Equal a b -- | A datatype representing type equality. The EQU constructor can be used -- to provide evidence that two types are equivalent. data Equal a b EQU :: Equal a a NEQ :: Equal a b instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.CC.Prompt.P ans m) instance GHC.Base.Monad m => Control.Monad.State.Class.MonadState GHC.Types.Int (Control.Monad.CC.Prompt.P ans m) instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.CC.Prompt.P ans) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.CC.Prompt.P ans m) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Monad.CC.Prompt.P ans m) instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.CC.Prompt.P ans m) -- | A monadic treatment of delimited continuations. -- -- Adapted from the paper A Monadic Framework for Delimited -- Continuations, by R. Kent Dybvig, Simon Peyton Jones and Amr Sabry -- (http://www.cs.indiana.edu/~sabry/papers/monadicDC.pdf) -- -- This module implements the generalized sequence type used as a stack -- of frames representation of the delimited continuations. module Control.Monad.CC.Seq -- | This is a generalized sequence datatype, parameterized by three types: -- seg : A constructor for segments of the sequence. -- -- ans : the type resulting from applying all the segments of the -- sequence. Also used as a region parameter. -- -- a : The type expected as input to the sequence of segments. data Seq seg ans a EmptyS :: Seq seg ans ans PushP :: Prompt ans a -> Seq seg ans a -> Seq seg ans a PushSeg :: seg ans a b -> Seq seg ans b -> Seq seg ans a -- | A type representing a sub-sequence, which may be appended to a -- sequence of appropriate type. It represents a sequence that takes -- values of type a to values of type b, and may be pushed onto a -- sequence that takes values of type b to values of type ans. type SubSeq seg ans a b = Seq seg ans b -> Seq seg ans a -- | Concatenate two subsequences appendSubSeq :: SubSeq seg ans a b -> SubSeq seg ans b c -> SubSeq seg ans a c -- | Push a sub-sequence onto the front of a sequence pushSeq :: SubSeq seg ans a b -> Seq seg ans b -> Seq seg ans a -- | Splits a sequence at the given prompt into a sub-sequence, and the -- rest of the sequence splitSeq :: Prompt ans b -> Seq seg ans a -> (SubSeq seg ans a b, Seq seg ans b) -- | A monadic treatment of delimited continuations. -- -- Adapted from the paper A Monadic Framework for Delimited -- Continuations, by R. Kent Dybvig, Simon Peyton Jones and Amr Sabry -- (http://www.cs.indiana.edu/~sabry/papers/monadicDC.pdf) -- -- This module implements the delimited continuation monad and -- transformer, using the sequence-of-frames implementation from the -- original paper. module Control.Monad.CC -- | The CC monad may be used to execute computations with delimited -- control. data CC ans a -- | Executes a CC computation, yielding a resulting value. runCC :: (forall ans. CC ans a) -> a -- | The CCT monad transformer allows you to layer delimited control -- effects over an arbitrary monad. -- -- The CCT transformer is parameterized by the following types -- -- data CCT ans m a -- | Executes a CCT computation, yielding a value in the underlying monad runCCT :: (Monad m) => (forall ans. CCT ans m a) -> m a data SubCont ans m a b -- | The prompt type, parameterized by two types: * ans : The region -- identifier, used to ensure that prompts are only used within the same -- context in which they are created. -- -- data Prompt ans a -- | A typeclass for monads that support delimited control operators. The -- type varibles represent the following: -- -- m : The monad itself -- -- p : The associated type of prompts that may delimit computations in -- the monad -- -- s : The associated type of sub-continuations that may be captured class (Monad m) => MonadDelimitedCont p s m | m -> p s -- | Creates a new, unique prompt. newPrompt :: MonadDelimitedCont p s m => m (p a) -- | Delimits a computation with a given prompt. pushPrompt :: MonadDelimitedCont p s m => p a -> m a -> m a -- | Abortively capture the sub-continuation delimited by the given prompt, -- and call the given function with it. The prompt does not appear -- delimiting the sub-continuation, nor the resulting computation. withSubCont :: MonadDelimitedCont p s m => p b -> (s a b -> m b) -> m a -- | Pushes a sub-continuation, reinstating it as part of the continuation. pushSubCont :: MonadDelimitedCont p s m => s a b -> m a -> m b -- | An approximation of the traditional reset operator. Creates a -- new prompt, calls the given function with it, and delimits the -- resulting computation with said prompt. reset :: (MonadDelimitedCont p s m) => (p a -> m a) -> m a -- | The traditional shift counterpart to the above reset. -- Reifies the subcontinuation into a function, keeping both the -- subcontinuation, and the resulting computation delimited by the given -- prompt. shift :: (MonadDelimitedCont p s m) => p b -> ((m a -> m b) -> m b) -> m a -- | The control operator, traditionally the counterpart of -- prompt. It does not delimit the reified subcontinuation, so -- control effects therein can escape. The corresponding prompt is -- performed equally well by reset above. control :: (MonadDelimitedCont p s m) => p b -> ((m a -> m b) -> m b) -> m a -- | Abortively captures the current subcontinuation, delimiting it in a -- reified function. The resulting computation, however, is undelimited. shift0 :: (MonadDelimitedCont p s m) => p b -> ((m a -> m b) -> m b) -> m a -- | Abortively captures the current subcontinuation, delimiting neither it -- nor the resulting computation. control0 :: (MonadDelimitedCont p s m) => p b -> ((m a -> m b) -> m b) -> m a -- | Aborts the current continuation up to the given prompt. abort :: (MonadDelimitedCont p s m) => p b -> m b -> m a instance Control.Monad.CC.MonadDelimitedCont (Control.Monad.CC.Prompt.Prompt ans) (Control.Monad.CC.SubCont ans Data.Functor.Identity.Identity) (Control.Monad.CC.CC ans) instance GHC.Base.Applicative (Control.Monad.CC.CC ans) instance GHC.Base.Monad (Control.Monad.CC.CC ans) instance GHC.Base.Functor (Control.Monad.CC.CC ans) instance GHC.Base.Monad m => GHC.Base.Functor (Control.Monad.CC.CCT ans m) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Monad.CC.CCT ans m) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.CC.CCT ans m) instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.CC.CCT ans) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.CC.CCT ans m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.CC.CCT ans m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.CC.CCT ans m) instance GHC.Base.Monad m => Control.Monad.CC.MonadDelimitedCont (Control.Monad.CC.Prompt.Prompt ans) (Control.Monad.CC.SubCont ans m) (Control.Monad.CC.CCT ans m) -- | An implementation of dynamically scoped variables using multi-prompt -- delimited control operators. This implementation follows that of the -- paper Delimited Dynamic Binding, by Oleg Kiselyov, Chung-chieh -- Shan and Amr Sabry (http://okmij.org/ftp/papers/DDBinding.pdf), -- adapting the Haskell implementation (available at -- http://okmij.org/ftp/packages/DBplusDC.tar.gz) to any delimited -- control monad (in practice, this is likely just CC and CCT m). -- -- See below for usage examples. module Control.Monad.CC.Dynvar -- | The type of dynamically scoped variables in a given monad data Dynvar m a -- | Creates a new dynamically scoped variable dnew :: MonadDelimitedCont p s m => m (Dynvar m a) -- | Reads the value of a dynamically scoped variable dref :: Dynvar m a -> m a -- | Assigns a value to a dynamically scoped variable dset :: Dynvar m a -> a -> m a -- | Modifies the value of a dynamically scoped variable dmod :: Dynvar m a -> (a -> a) -> m a -- | Calls the function, g, with the value of the given Dynvar dupp :: Dynvar m a -> (a -> m b) -> m b -- | Introduces a new value to the dynamic variable over a block dlet :: Dynvar m a -> a -> m b -> m b -- | Implements various cursor datatypes for iterating over collections module Control.Monad.CC.Cursor -- | A generalized type that represents a reified data structure traversal. -- The other traversal data types in this module are special cases of -- this general type. Cursor is parameterized by four types: -- -- m : The monad in which the Cursor object is usable. -- -- r : The result type, which will be stored in the cursor once the -- traversal has been completed. -- -- b : The type that the cursor expects to receive before moving on to -- the next element in the traversal. -- -- a : The element type to which the Cursor provides access at each step -- in the traversal. data Cursor m r b a Current :: a -> (b -> m (Cursor m r b a)) -> Cursor m r b a Done :: r -> Cursor m r b a -- | A simple iterator, which provides a way to view each of the elements -- of a data structure in order. type Iterator m a = Cursor m () () a -- | A function for making a cursor out of a free form generator, similar -- to using yield in Ruby or Python. For example: -- --
--   generator $ \yield -> do a <- yield 1 ; yield 2 ; b <- yield 3 ; return [a,b]
--   
generator :: MonadDelimitedCont p s m => ((a -> m b) -> m r) -> m (Cursor m r b a) -- | Creates an Iterator that will yield each of the elements of a Foldable -- in order. iterator :: (Foldable t, MonadDelimitedCont p s m) => t a -> m (Iterator m a) -- | Extracts the current element from a cursor, if applicable. current :: Cursor m r b a -> Maybe a -- | Advances an Iterator to the next element (has no effect on a finished -- Iterator). next :: Iterator m a -> m (Iterator m a) -- | Begins an updating traversal over a Traversable structure. At each -- step, the cursor will hold an element of type a, and providing an -- element of type b will move on to the next step. When done, a new -- Traversable object holding elements of type b will be available. open :: (Traversable t, MonadDelimitedCont p s m) => t a -> m (Cursor m (t b) b a) -- | Provides an item to a Cursor, moving on to the next step in the -- traversal. (has no effect on a finished Cursor). update :: b -> Cursor m r b a -> m (Cursor m r b a)