[Haskell] Three new implementations of multi-prompt delimited control

oleg at okmij.org oleg at okmij.org
Wed Sep 1 04:04:16 EDT 2010


The monadic framework for delimited continuations described in
the paper by Dybvig, Peyton Jones and Sabry (JFP 2007) has found
many applications, for example, fair backtracking search, final
zippers, direct-style web programming, direct-style code generation,
and probabilistic programming. The extensive experience suggested
improvements in efficiency and, mainly, programmer's convenience. The
three new libraries are novel implementations of the enhanced
framework. Prompts, for instance, can now be bound to top-level
identifiers and do not have to be passed around explicitly or through
the extra Reader monad.  The new libraries benefited from the
experience of implementing delimited control on several platforms.

All three libraries provide monad transformers, with basic operations
to capture and reinstall delimited continuations: pushPrompt, shift,
shift0, control, takeSubCont/pushSubCont.  All three libraries support
multiple, typed prompts. All three libraries are quite distinct from
the original implementation in Dybvig, Peyton Jones, Sabry's
paper. For instance, none of the new libraries use unsafeCoerce.  All
three implementations are derived from the specification of delimited
control: from the reduction semantics or from the definitional
interpreter.

The new libraries differ in
  -- performance
  -- ease of understanding
  -- constraints on the base monad or the prompt types
  -- flavors of prompts and support for global prompts

The libraries are named CCRef, CCExc and CCCxe. The complete code
of the libraries along with the regression test suite are publicly
available at
	http://okmij.org/ftp/continuations/CCmonad/
The directory includes sample code (Generator1.hs and Generator2.hs),
implementing generators like those of Python. A more extensive
example is the porting of the LogicT library (of fair backtracking
monad transformers), from the old CC implementation to CCExc/CCCxe:
	http://okmij.org/ftp/Haskell/LogicT.tar.gz
One of the sample applications of LogicT, of a computer playing 
5x5 tic-tac-toe against itself, was used as a macro-benchmark of the
libraries. The end of the file TicTacToe.hs summarizes the results.
The new libraries are faster (so the reader who may wish to play 
will have less time to think).


The library CCRef is closest to the interface of Dybvig, Peyton Jones
and Sabry. CCRef is derived from the definitional interpreter using the
implementation techniques described and justified in the FLOPS 2010
paper. The monad transformer CC implemented by CCRef requires the base
monad to support reference cells. In other words, the base monad must
be a member of the type class Mutable: that is, must be IO, ST, STM or
their transformer. CCRef adds to the original interface the frequently
used function abortP as a primitive.

As one may notice from their names, the libraries CCExc and CCCxe are
closely related. CCCxe is derived as a CPS version of CCExc.  CCCxe is
sometimes more efficient; it is always less perspicuous. Both
libraries provide the identical interface and are interchangeable. It
seems that CCExc is faster at delimited control but imposes more
overhead on the conventional code; CCCxe is dual. It pays to use CCCxe
in code with long stretches of determinism punctuated by fits and
restarts.

We now explain new features of CCExc. It is the most direct
implementation of the bubble-up (bottom-up) reduction semantics of
multi-prompt delimited control, described on
PDF page 57 of http://okmij.org/ftp/gengo/CAG-talk.pdf

Unlike all other implementations of delimited control in Haskell,
CCExc is _not_ based on the continuation monad. Rather, the monad of
CCExc is an extension of the Error monad: a monad for restartable
exceptions. CCExc offers not one monad transformer but a family (CC
p), parameterized by the prompt flavor p. The library defines several
prompt flavors; the users are welcome to define their own.

Prompt flavors are inherently like exception flavors (the FLOPS 2010
paper even calls prompts `exception types' or `exception envelopes').
Control.Exception defines singular global exceptions such as
BlockedOnDeadMVar.  There are global exceptions like ErrorCall,
parameterized by the error string. There are closed global variants,
such as ArithException, with the fixed number of alternatives. There
are also open variants, SomeException, with any number of potential
alternatives. Users may define their own exception types, whose
visibility may be restricted to a module or a package. Finally, one
may even generate distinct expression types dynamically, although that
is seldom needed.

The libraries CCExc and CCCxe support all these flavors. On one end is
the prompt flavor (PS w). There is only one prompt of that flavor,
which is globally defined and does not have to be passed around.  The
monad transformer (CC (PS w)) then is the monad transformer for
regular, single-prompt delimited continuations, for the answer-type w.
Danvy/Filinski test, which looks in Scheme as

> (display (+ 10 (reset (+ 2 (shift k (+ 100 (k (k 3))))))))

appears as follows in Haskell:

> test5 = (print =<<) . runCC $
>   incr 10 . pushPrompt ps $
>      incr 2 . shiftP ps $ \sk -> incr 100 $ sk =<< (sk 3)

where
>   incr :: Monad m => Int -> m Int -> m Int
>   incr n = ((return . (n +)) =<<)

[A reader might wish to try to predict the result of test5.]
The global identifier ps is defined in CCExc.

One should read the operator (=<<), the flipped bind, as a
``call-by-value application'', akin to the application in CBV
languages such as Scheme. That is, "f =<< e" is the application that
first evaluates the argument e, performing its effects. The value is
passed to f, which is evaluated in turn. The application "sk 3" is an
optimized version of "sk =<< (return 3)".

The appearance of print tells us that test5 is the IO computation. If
we rather had the result of test5 as a pure value (an integer), we
merely need to pass the result of the runCC expression to runST.

The file Generator1.hs shows one example of using PS; the file
SRReifT.hs of the LogicT is a larger example.

The file Generator2.hs demonstrates why we may need more than one prompt
(perhaps with different types). The library offers several flavors of
multiple prompts: closed unions (P2) and open unions (PP, PM, PD).
The open unions are like SomeException. The prompt flavor PD carries
an extra integer identifier to further distinguish prompts of the
same type. It becomes possible therefore to dynamically generate an
arbitrary number of PD prompts, which was required in Dybvig,
Peyton Jones and Sabry's framework.

We close by juxtaposing the Python code that uses generators to
traverse a binary tree in-order

>>> def inorder(t):
...     if t:
...         for x in inorder(t.left):
...             yield x
...         yield t.label
...         for x in inorder(t.right):
...             yield x

with the corresponding Haskell code (excerpted from Generator1.hs)

> in_order :: (Monad m) => Tree -> CC (P m Label) m ()
> in_order Leaf = return ()
> in_order (Node label left right) = do
>     in_order left
>     yield label
>     in_order right

In Python, 'yield' is a keyword and generators are built-in. 
In Haskell, yield is a regular, small, user-defined function, and
generators are programmed-in.



More information about the Haskell mailing list