On this page:
8.1 Continuation-passing style
8.2 Exception handling
8.3 Undelimited continuations
8.4 Delimited continuations
8.5 Racket’s implementation of continuations
8.1

8 Continuations

\(\newcommand{\la}{\lambda} \newcommand{\Ga}{\Gamma} \newcommand{\ra}{\rightarrow} \newcommand{\Ra}{\Rightarrow} \newcommand{\La}{\Leftarrow} \newcommand{\tl}{\triangleleft} \newcommand{\ir}[3]{\displaystyle\frac{#2}{#3}~{\textstyle #1}}\)

In this chapter (which you should consider optional reading), we return to the idea of continuations, the data structure we used in the previous chapter to make our Faux Racket interpreter tail-recursive, and show how they can be used to implement a number of useful language features, including threads with message-passing concurrency.

I developed this material as a suitable conclusion to my two-course sequence, which ended with us up in the clouds rather than down in the mud. I hope you will feel similarly about it.

8.1 Continuation-passing style

Our continuation data structure saves information needed for a later computation. The computation is eventually completed using applyCont, which applies the continuation to a value.

This sounds familiar: like a lambda with one argument. In fact, in a language that lacks functions as values, this is exactly what needs to be done to adapt techniques that use lambda. But in a functional language, we can turn that idea on its head, and use lambda to represent continuations.

To illustrate the technique, let’s consider a simpler example: structurally-recursive factorial.

(define (fact n)
  (cond
    [(= n 1) 1]
    [else (* n (fact (sub1 n)))]))

Given the result r of (fact (sub1 n)), the rest of the computation is (* n r). We can express this in a self-contained form as (lambda (r) (* n r)).

We add the continuation to the function as an extra accumulative parameter k. In the base case, we apply k to the value we would have produced, to do the rest of the computation.

In the recursive case, we add to the continuation accumulator. But we do need to add to it, not replace it. So (lambda (r) (* n r)) isn’t all of the rest of the computation; (lambda (r) (k (* n r))) is.

If we do this systematically, we make the function tail-recursive. We must also supply an initial continuation, which is the identity function. Here is the result.

(define (fact n)
  (local (
    (define (fact/k n k)
      (cond
        [(= n 1) (k 1)]
        [else (fact/k (sub1 n) (lambda (r) (k (* n r))))])))
   (fact/k n (lambda (r) r))))

This style of programming is known as continuation-passing style, or CPS. For another example, we can use structurally-recursive Fibonacci.

(define (fib n)
  (cond
    [(= n 0) 0]
    [(= n 1) 1]
    [else (+ (fib (- n 1))
             (fib (- n 2)))]))

Here is the result of applying CPS.

(define (fib/k n k)
  (cond
    [(= n 0) (k 0)]
    [(= n 1) (k 1)]
    [else
     (fib/k (- n 1)
            (lambda (r1)
              (fib/k (- n 2)
                     (lambda (r2)
                       (k (+ r1 r2))))))]))

We could have created our continuation-passing interpreter by applying CPS to the naive interpreter, then converting the lambda representation of continuations to a data structure representation.

Let’s return to the CPS version of factorial and take a closer look at the continuations.

(define (fact n)
  (local (
    (define (fact/k n k)
      (cond
        [(= n 1) (k 1)]
        [else (fact/k (sub1 n) (lambda (r) (k (* n r))))])))
   (fact/k n (lambda (r) r))))

It’s not hard to see that the continuation k is always of the form (lambda (r) (* m r)) for some integer m. We can just use the integer m in the accumulator.

(define (fact n)
  (local (
    (define (fact/a n m)
      (cond
        [(= n 1) m]
        [else (fact/a (sub1 n) (* n m))])))
   (fact/a n 1)))

By using CPS, we have transformed structurally-recursive factorial into tail-recursive factorial, such as we might have written in Part 1.

Does this technique work for converting inefficient structurally-recursive Fibonacci into efficient tail-recursive Fibonacci?

No!

This technique converts inefficient structurally-recursive Fibonacci into inefficient tail-recursive Fibonacci. CPS only changes the way a computation is expressed. It does not change the operations performed.

Conversion to CPS is simple enough that it can be automated (by recursion on an AST, or even by using macros). There are many different CPS transformations. It is easier to see how to compile code using CPS to machine code. Some important compilers for functional languages use a CPS transformation as an intermediate step. Alternately, one can modify the continuation-passing interpreter to emit machine code instead of doing evaluation.

Hand-built continuations have many uses. If a function needs to produce multiple values, we can pass it a continuation that consumes those values. Another use of a hand-built continuation argument could be as something to be applied if a function "fails" (for example, a lookup).

Continuations turn out to be useful in dealing with situations where computation is interrupted and then resumed. One example is Web client-server interaction. The popular Node.js framework encourages programmers to use CPS with JavaScript. For more details, see the article "By example: Continuation-passing style in JavaScript: on Matt Might’s blog.

8.2 Exception handling

Our continuation-passing interpreter can be used as a helper function in larger contexts. For example, we could create a REPL using it. It might look something like this (here for clarity we have used display instead of printf, not printed a prompt, and left out the initial values of accumulative parameters in the application of interp):

(define (repl)
  (display (interp (read) ...))
  (repl))

But if the interpreter raises an error using error, it stops the whole REPL, whereas we’d prefer it to give us a chance to try again. At the point that the error is raised, the continuation represents the rest of the evaluation of the original expression.

The interpreter could simply print an error message (using printf, not error) and produce the empty string, ignoring the continuation. But this only works if the error is found by interp. What if it is found in some helper function (like lookup) that isn’t part of the main tail-recursive computation?

Racket provides a more general mechanism that lets us continue to use error in a natural way. It defines exceptions, which include errors. As an example of a non-error exception, one is raised when the user breaks (requests that a running program stop).

In Racket, any raised exception can be caught. An exception creates a value with associated information. The error function creates a exn:fail struct to hold the associated information (in this case the error message).

The value raised by an exception can be caught by a handler function. The with-handlers form allows us to specify various handler functions to catch different exceptions.

The with-handlers form resembles cond in pairing exception tests with associated handlers. But the tests are predicates applied to the value raised by the exception, and the handlers are functions consuming the value raised.

(define (repl)
  (with-handlers
    ([exn:fail?
       (lambda (e)
        (display (exn-message e))
        (repl))])
   (display (interp (read) ...))
   (repl)))

Informally, evaluating a with-handlers expression adds the set of handler tests to a stack. When an exception is raised, the topmost (most recent) set of tests is tried first. If a test passes, the raised value is given to the handler, and the result it produces becomes the result of its with-handlers expression. There is a default handler installed at the top level in case a raised exception fails all handler tests.

Note that the mechanism determining the order of handler tests is dynamic, not lexical. Two with-handlers expressions can be nested in code, but a function applied in the outer body but before the inner with-handlers is evaluted could install a third set of handler tests between the other two.

To clarify, we will model a simpler construct, introduced in R2RS Scheme (1985), by adding it to our Faux Racket interpreter. We add two language constructs to Faux Racket, throw and catch. Informally, catch specifies a handler expression and a body expression. The handler expression is evaluated to produce a lambda, and then the body expression is evaluated.

If, during the evaluation of the body expression, throw is applied to a value, then this raises an exception. The handler is applied to that value, and the result becomes the value of the catch expression.

(catch
  (lambda (x) B)
  (... (throw v) ...))
=> ((lambda (x) B) v)

Of course, throw may never be applied in the body expression, if that computation does not raise an exception.

(catch (lambda (x) B) v) => v

It is an error to apply throw outside the context of an enclosing catch expression.

Racket provides equivalents for these language features (raise and call-with-exception-handler) but the with-handlers mechanism is more general and useful.

Adding support for catch and throw to the continuation-passing interpreter is not difficult. To evaluate (catch H E), the handler expression H must be evaluated first. We need a new continuation struct, k-catchL, which holds the body expression, the current environment, and the previous continuation k. (Our previous code was in Haskell, but since I am not giving code here, I have switched to Racket for the explanation. One datatype variant in Haskell corresponds to one struct in Racket.)

When apply-cont is given a k-catchL, it produces a k-catchR holding the environment, the handler value, and k, and evaluates the body expression.

If a throw does not take place in the evaluation of the body, apply-cont is eventually applied to the k-catchR and the body value. But if interp is applied to a throw expression, the argument expression needs to be evaluated (using another continuation struct, k-throw).

When apply-cont is given a k-throw, it unwinds the continuation it contains until it finds the k-catchR, which contains the information needed to continue the computation.

Exercise 28: Add exceptions to the interpreter you wrote for exercise 26. \(\blacksquare\)

The search through the continuation to find the catch can be slow, and there are more efficient implementations. Racket uses a more general primitive mechanism, which we will discuss later.

8.3 Undelimited continuations

A continuation resembles a function. We have created apply-cont in order to apply a continuation to a value. What if the continuation were made available to the interpreted program?

Racket has a way of binding a name to the current continuation, using let/cc. (Scheme uses call/cc, which consumes a function and applies that function to the current continuation.)

Scheme made the choice of using regular function application to apply a continuation to a value, and Racket continues that tradition. This is not the case in some other functional languages. For example, the ML language augments throw with a continuation argument, essentially exposing apply-cont.

But, in choosing to use regular function application to apply continuations, we run into some issues. A continuation is not exactly like a lambda. Consider the evaluation of the following expression.

(* 2 (let/cc k (+ 4 (k 3))))

The continuation, when the let/cc becomes the redex, looks like (lambda (r) (* 2 r)).

But using a captured continuation replaces the current continuation. This does not happen for lambda. Here is the way lambda works:

(...
  ((lambda (x) exp) arg)
 ...)
=>
(...
  exp-with-subst
 ...)

This is the substitution rule from Part I, with ellipses to indicate the context, which is preserved.

When a continuation is used, the context is erased. We use lambda^ (pronounced "lambda-hat") to denote an escape procedure, which has this effect on the context. Here is the effect of applying lambda^.

(...
  ((lambda^ (x) exp) arg)
 ...)
=>
  exp-with-subst

Note that the context is destroyed in the rewrite, unlike the rule given above. Here is how a trace of our example for let/cc would look in the substitution model.

(* 2 (let/cc k (+ 4 (k 3))))
=>
(* 2 (+ 4 ((lambda^ (x) (* 2 x)) 3)))
=> (* 2 3) => 6

This is less than satisfactory, as it introduces something (lambda-hat) into intermediate expressions that is not available in the original language.

Undelimited continuations (call/cc) were introduced in R3RS Scheme after their appearance in a significant implementation, Scheme 311, at Indiana University.

Here’s how we might implement something like catch using let/cc, followed by an example of its use. In this example, the try function consumes two arguments. The first argument of try is a function fexp which does some computation. fexp consumes a "fail" continuation to be applied if the computation has to be aborted due to some error. The second argument of try function is a handler function that is applied to the argument of the fail continuation. The result of this is the result of the try expression. Of course, if the fail continuation is never used, then the result of fexp should be the result of the try expression. The example (catching division by zero) should make this more clear.

(define (try fexp handler)
  (let/cc succ
    (handler
      (let/cc fail
        (succ (fexp fail))))))
 
(define (div x y)
  (try
   (lambda (f) (if (zero? y)
                   (f "division by zero")
                   (/ x y)))
   (lambda (m) (display "naughty\n") x)))

The code for try is short but seems puzzling at first. Try tracing it, either informally, or using the semantics for let/cc expressed in terms of lambda^.

Implementing letcc in our continuation-passing interpreter is again straightforward. We create a struct to hold a continuation.

(struct lambda-hat (cont))

Evaluating a letcc will add a binding to the environment of the variable to a lambda-hat holding the current continuation.

Function application now has to work on closures and lambda-hats both. To apply a lambda-hat, we use apply-cont.

Exercise 29: Add undelimited continuations to the interpreter you wrote for exercise 26. \(\blacksquare\)

8.4 Delimited continuations

Lambda-hats are frustrating, because they destroy context. One cannot compose them as one can with lambdas. There are also problems combining their use with exception handling and other language constructs.

A more sophisticated mechanism extends our earlier implementation of catch and throw. Recall that throw unwound the continuation, throwing away frames until it reached the k-catchR.

(catch
  (lambda (x) B)
  (... (throw v) ...))
=>
((lambda (x) B) v)

The argument of the handler, when it is invoked by throw, is the value thrown.

We can add a second argument to the handler that represents the previously-discarded continuation frames. (Once we add multiple arguments to functions in our interpreter, that is.) This mechanism can be used to, for example, continue the computation that caused the error, after fixing the error condition in some fashion, instead of just aborting it.

This is known as a delimited continuation, because it only contains a portion of the remaining computation, not all of it.

Unwinding the continuation corresponds to ascending in the expression we would have in the substitution model. Conceptually, we can start with a fresh variable z, and as we unwind the continuation, we reconstruct the expression. When we reach the k-catchR, we wrap the expression in
(lambda (z) ...)
and supply that to the handler as its second argument.

More practically, we can save the removed continuation frames and put them in a comp-cont structure (for composable continuation). To apply a comp-cont to a value, we put the saved continuation on top of the current continuation, and then apply the new continuation to the value.

Exercise 30: Add delimited computations to the interpreter you wrote for exercise 26. \(\blacksquare\)

This is the basis of Racket’s implementation, though Racket uses a more general mechanism. The racket/control module provides catch and the augmented version of throw, though they are given the names % and fcontrol respectively (from the original paper by Sitaram).

The racket/control module also provides many other control operators that appear in the literature. The ones you are likely to encounter are shift and reset (Danvy & Filinski, 1990). These resemble throw and catch, but the handler is specified with shift. The handler also automatically reinstalls the prompt, ensuring that these operators can be reasoned about statically (lexically).

Undelimited continuations can simulate delimited continuations, and vice-versa. The same is true for the various types of control operators. Where they differ is in expressivity.

Delimited continuations allow nonstandard flow of control. They can be used to implement ideas like generators, coroutines, threads, and engines. Racket has support for these.

8.5 Racket’s implementation of continuations

The Racket documentation uses the term continuation frame for the equivalent to our continuation structs. A special kind of continuation frame called a prompt is the equivalent of a k-catchR. It represents a delimiter for continuations.

The call/prompt function adds a prompt to the current continuation, and applies a specified function to specified arguments. (call/prompt is short for call-with-continuation-prompt.) Optionally, call/prompt accepts a tag and a handler function (otherwise a default tag created by default-continuation-prompt-tag is used).

The abort/cc function (short for abort-current-continuation) unwinds the current continuation to a specified tag (installed by something like call/prompt) and provides the rest of its arguments to the handler that was installed with the tag.

The call/cc function, in Racket’s implementation, also accepts an optional tag argument (with a default value). It does not capture its continuation beyond a correspondingly tagged prompt. In the discussion above (and in other Scheme implementations), the continuation captured by call/cc, when applied, destroys all context (discards the continuation at point of application). Now it destroys context up to a correspondingly tagged prompt.

The call/comp function (short for call-with-composable-continuation) is like call/cc, but the captured continuation does not destroy context when applied. That is, a continuation captured by call/comp can be described by lambda, rather than a tag-sensitive lambda^.

These primitives suffice to implement the other constructs we have discussed, and other control operators provided by racket/control. As an example, here are implementations of the most general versions of catch and throw above.

(define-syntax-rule (catch handler body)
  (call-with-continuation-prompt
    (lambda () body)
    (default-continuation-prompt-tag)
    handler))
 
(define (throw v)
  (call-with-composable-continuation
    (lambda (k)
      (abort-current-continuation
        (default-continuation-prompt-tag)
        k
        v))))

Racket also supports adding continuation marks to any continuation frame. Each mark is a key-value pair. These provide support for the Stepper, debugging, handling parameters properly in the presence of continuations, and various other features. For details, see "Adding Delimited and Composable Control to a Production Programming Environment" (Flatt et al., ICFP 2007).

As an example, we will consider the implementation of generators. The version I’ll describe is not as sophisticated as the ones implemented by the module racket/generator, which you can learn about in the Racket documentation.

Given a way of creating a sequence of values (say, by traversing a list or tree), we would like to create an alternate version that delivers the values one at a time, on demand. Here is an example of the desired behaviour.

(define g
  (make-gen
   (for-each yield '(1 2 3 4))))
(g)
> 1
(g)
> 2

To avoid having to write a macro which provides a binding for yield, we use the same idea as call/cc and call/comp, namely we will have the argument make-gen be a (lambda (yield) ...), or a function that consumes a yield function. Here is the example changed to use this version of make-gen.

(define g
  (make-gen
    (lambda (yield)
      (for-each yield '(1 2 3 4)))))
(g)
> 1
(g)
> 2

The implementation of make-gen is remarkably simple using Racket’s support for delimited and composable continuations.

(define (make-gen f done)
  (define tag (make-continuation-prompt-tag))
  (define (yield v) (call/comp (lambda (k) (abort/cc tag k v)) tag))
  (define (cache) (f yield) done)
  (define (handler k v) (set! cache k) v)
  (lambda () (call/prompt cache tag handler)))

As an example of the use of generators, consider a situation where a tree is represented by an S-expression. The leaves or fringe of the tree represent some linearly-ordered (left to right) information (like the text of a book), and the internal nodes represent grouping (into sections, chapters, etc.). We want to compare two such trees to see whether their fringes are equal or different.

The easiest thing to do is to flatten the two trees into lists and then compare the lists.

(define (flatten s)
  (cond
    [(empty? s) empty]
    [(cons? s) (append (flatten (first s)) (flatten (rest s)))]
    [else (list s)]))

But if the trees are large, and the differences are early in the fringes, this is inefficient. Can we create code that only does necessary work but which still expresses the idea of the computation elegantly?

What we will do is create a generator of the fringe of a tree.

(define (make-fringe-gen sexp done)
  (make-gen
    (lambda (yield)
      (define (fringe s)
        (cond
          [(empty? s) (void)]
          [(cons? s) (fringe (first s)) (fringe (rest s))]
          [else (yield s)]))
      (fringe sexp))
    done))

To compare two fringes, we sample from each generator, and compare the samples.

(define (equal-fringe? s1 s2)
  (define g1 (make-fringe-gen s1 empty))
  (define g2 (make-fringe-gen s2 empty))
  (define (fringe-iter)
    (define from-s1 (g1))
    (define from-s2 (g2))
    (cond
      [(and (empty? from-s1) (empty? from-s2)) true]
      [(or (empty? from-s1) (empty? from-s2)) false]
      [(not (equal? from-s1 from-s2)) false]
      [else (fringe-iter)]))
  (fringe-iter))

Generalizing further, we can write a function that trampolines between two generators, say a producer and consumer that operate at unpredictable rates. The yielded values are irrelevant in this case; it is the context switch that is important. The two generators can communicate information through shared mutable global variables. Each of the two generators in this situation is classically called a coroutine.

There is no reason to stop at two. The trampoline function or scheduler can manage several generators, each being considered a thread. This concept of several computations running in an interleaved fashion is known as concurrency. Only one thread is executing at a time, however, so this is not parallelism.

Again, using continuations, we get a very simple implementation. It turns out that using undelimited continuations gives the shortest implementation (though delimited continuations work better with other features).

We’ll use a simple scheduling idea: first-in, first-out. This is the discipline used when lining up to buy something in a store, and the data structure is called a queue. Racket provides an implementation in data/queue, but we can write our own using mutable lists.

(struct queue (head tail) #:mutable)
 
(define (new-queue) (queue empty empty))
 
(define (empty-queue? queue) (empty? (queue-head queue)))
(define (nonempty-queue? queue) (not (empty-queue? queue)))
 
(define (enqueue v queue)
  (let ((newpair (mcons v empty)))
    (if (empty-queue? queue)
         (set-queue-head! queue newpair)
         (set-mcdr! (queue-tail queue) newpair))
    (set-queue-tail! queue newpair)))
 
(define (dequeue queue)
  (begin0 (mcar (queue-head queue))
          (set-queue-head! queue (mcdr (queue-head queue)))))

Because the data structure is so simple, we can get rid of the scheduler in this case, by having the handler function store one continuation in the queue and resume another one.

The function spawn that consumes a thunk (a function of no arguments). It suspends the current thread and starts a new one that executes the thunk. The function yield suspends the current thread and starts another.

(define threads (new-queue))
 
(define (spawn t)
  (let/cc k (enqueue k threads) (t) (done)))
 
(define (yield)
  (let/cc k (enqueue k threads) (done)))
 
(define (dispatch) ((dequeue threads)))
 
(define (done)
  (if (nonempty-queue? threads)
      (dispatch)
      (error "no more threads")))

The point of doing this is increased expressivity. The code for a thread is in one place, instead of being chopped up into segments at yield points. Another type of computation with multiple yield points is a web transaction. A yield represents the need for the server to get information from the client (say through a posted form). The web server in the Racket distribution uses continuations to express such transactions in a natural fashion.

Mutating global variables is not a very good way for threads to communicate. We could build on the direct communication we had with yield in generators to implement message passing using channels.

A channel is conceptually a queue of messages. A thread can send a message to the end of the queue (we will consider this as a yield point) or can try to receive from the front of the queue. But what happens if the queue is empty? We could ask the receiver to come back later, but this tends to lead to lots of repeated asking. Instead, we will have the receiver block until a message arrives for it. This means that the implementation of a channel maintains two queues: a queue of blocked receivers, and a queue of sent messages. (Only one of these can be non-empty, but it’s confusing to write code where what’s on the queue keeps changing.)

(struct chan (recv send))
(define (channel)
  (chan (new-queue) (new-queue)))
 
(define (send c msg)
   (let/cc k
    (cond
      [(empty-queue? (chan-recv c))
         (enqueue k threads)
         (enqueue msg (chan-send c))
         (dispatch)]
      [else
         (enqueue k threads)
         ((dequeue (chan-recv c)) msg)])))
 
(define (receive c)
  (cond
    [(empty-queue? (chan-send c))
      (let/cc k
        (enqueue k (chan-recv c))
        (dispatch))]
    [else
      (dequeue (chan-send c))]))

We could continue along these lines: we could implement conditional receiving so that a receiver can pick out a message sent to it, or we could give each thread its own mailbox. These ideas were developed in Concurrent ML, which is built on top of undelimited continuations in ML. Racket’s sophisticated implementation of threads uses a very similar framework. Just as avoiding mutation leads to code that is easier to develop, reason about, and maintain, message-passing concurrency avoids many of the problems associated with concurrency based on mutating shared memory.