Explicit and Implicit

Consider two kinds of video games. The first are 80s-style cabinets, that might suppress most awareness of your outside environment, but you can still directly perceive the controls, the "new game" button, and so on:

star-wars-arcade.gif

The second are more immersive games with VR goggles and gloves:

virtual-reality.jpg

In this second kind of game, you don't see or feel the goggles or gloves (anyway, you don't perceive them as goggles or gloves), and you needn't normally perceive any "new game" button. But the game might have some "magic gesture" you can perform, such as holding your left elbow while simultaneously stamping your right foot twice, that would invoke a special menu in your visual display, containing among other things a "new game" button.

I want to offer the contrast between these two kinds of games, and the ways that you can perceive and handle the "new game" button, as analogy for the contrast between explicit and implicit mutation, which we looked at earlier, and also the contrast between explicit and implicit continuations, which we're beginning to look at now.

With explicit mutation operators in the language, our code looks like this:

let x = cell 0 in
... get x ...
... put 1 into x ...

With implicit mutation operators in the language, it looks instead like this:

var x = 0 in
... x ...
... x := 1 ...

The first two lines aren't very different from what we'd have without mutation:

let x = 0 in
... x ...

The first line used the keyword var instead of the more familiar let, but that's just to signal that the variable we're introducing is mutable. Syntactically it acts just like a variant spelling of let. Also we access the contents of the variable in the same way, with just x. Whereas with the explicit reference cells, we have to say get x. There we can "see" the reference cell and have to explicitly "look inside it" to get at its contents. That's like seeing the "new game" button and other controls during the normal use of the video game. In the third line of the implicit mutation code, we have the "magic gesture", x := 1, which does something you couldn't do in the code without mutation. This is like bringing up the "new game" display by the magic elbow-and-stomping gesture, which doesn't work in real life. This lets us achieve the same effect that we did in the explicit code using put 1 into x, but without us needing to (or being able to) explicitly inspect or manipulate the reference cell itself.

Turning to continuations, so far we've seen how to explicitly manipulate them, as in:

let rec tc (xs : char list) (k : char list -> char list) =
  ... tc xs' (fun tail -> ... k ... tail) in
tc some_list identity

Here we explicitly pass around continuations in the k argument, beginning with the identity or do-nothing continuation, but then modifying the continuation at each recursive invocation of tc.

What the continuation or control operators like let/cc, reset, shift, abort, and so on do is give us a "magic gesture" alternative, where we can let the continuations usually be implicit in the way our code is structured, but when we perform the magic gesture (that is, use some of these special operators), the continuation gets converted from its implicit form into an explicit function that's bound to a variable we supply.

A Bestiary of operators for magically distilling implicit continuations into explicit functions

The continuation operators come in a variety of forms. You'll only be using a few of them (if any) in a single application. But here we'll present a couple of them side-by-side.

One issue is whether the continuation operators you're working with are "full-strength" or not. As we said, what these operators do is distill an implicit continuation into a function that you can explicitly invoke or manipulate (pass into or return from a function). If they're "full-strength", then there aren't constraints on where or how many times you can invoke that continuation function. Anywhere you have access to some variable that's bound to the continuation, you can invoke it as often as you like. More handicapped continuations are only invocable a single time, or only in certain regions of the code. Sometimes these handicapped continuations are provided because they're easier to implement, and the language designers haven't gotten around to implementing full-strength continuations yet. Or a language might provide both handicapped and full-strength continuations, because the former can be implemented more efficiently. For applications like coroutines or exceptions/aborts, that we looked at before, typically all that's needed is a handicapped form of continuations. If your language has an abort operation, typically you'll only be invoking it once within a single execution path, and only inside the box that you want to abort from.

For our discussion, though, we'll just be looking at the full-strength continuations. You can learn about different ways they might be handicapped later.

The next issue is whether the continuations are delimited or not. In our discussion of aborts, we had a box, and what abort did was skip the rest of the code inside the box and resume execution at the outside border of the box. This is the pattern of a delimited continuation, with the box being the delimiter. There are a bunch of different operators that have been proposed for dealing with delimited continuations. Many of them are interdefinable (though the interdefinitions are sometimes complex). We won't be trying to survey them all. The ones we'll suggest as a paradigm are the pair of reset and shift. The first of these marks where the box goes, and the second has two roles: (i) it marks where you should start skipping (if you're going to "skip the rest of the code inside the box"), and (ii) it specifies a variable k that we bind to the continuation representing that skipped code. Thus we have:

initial outside code
+---reset--------------------+
| initial inside code        |
| shift k. ( ... )           |
| remaining inside code      |
+----------------------------+
remaining outside code

Really in the implementation of this there are two continuations or snapshots being tracked. There's the potentially skipped code, represented by remaining inside code above; and there's also the continuation/snapshot that we resume with if we do skip that code, represented by remaining outside code. But only the first of these gets bound to a variable, k in the above diagram. What happens in this diagram is that initial outside code runs, then initial inside code runs, then remaining inside code is distilled into a function and bound to the variable k, then we run the ( ... ) code with k so bound. If that ( ... ) code invokes k by applying it to an argument, then remaining inside code is run as though the supplied argument were what the shift k. ( ... ) bit evaluated to. If the ( ... ) code doesn't invoke k, but just ends with a normal result like 10, then the remaining inside code is skipped and we resume execution with the outside, implicitly snapshotted code remaining outside code.

You may encounter references to prompt and control. These are variants of reset and shift that differ in only subtle ways. As we said, there are lots of variants of these that we're not going to try to survey.

We talked before about abort. This can be expressed in terms of reset and shift. At the end of our discussion of abort, we said that this diagram:

let foo x =
+---try begin----------------+
|       (if x = 1 then 10    |
|       else abort 20        |
|       ) + 100              |
+---end----------------------+
in (foo 2) + 1000;;

could be written in Scheme with either:

#lang racket
(require racket/control)

(let ([foo (lambda (x)
             (reset
              (+
                (if (eqv? x 1) 10 (abort 20))
                100)))])
  (+ (foo 2) 1000))

or:

#lang racket
(require racket/control)

(let ([foo (lambda (x)
             (reset
              (+
                (shift k
                  (if (eqv? x 1) (k 10) 20))
                100)))])
  (+ (foo 2) 1000))

That shows you how abort can be expressed in terms of shift. (Notice that with abort, there's a special keyword used in the aborting branch but no keyword in the "continue normally" branch; but with shift it's the converse.) Rewriting the Scheme code into a more OCaml-ish syntax, it might look something like this:

let foo x = reset (shift k -> if x = 1 then k 10 else 20) + 100) in
foo 2 + 1000

However, OCaml doesn't have any continuation operators in its standard deployment. If you installed Oleg's delimcc library, you can use the previous code after first doing this:

# #directory "+../delimcc";;
# #load "delimcc.cma";;
# let reset_label = ref None;;
# let reset body =
    let p = Delimcc.new_prompt () in
    let oldp = !reset_label in
    reset_label := Some p; let res = Delimcc.push_prompt p body in
    reset_label := oldp; res;;
# let shift fun_k = match !reset_label with
  | None -> failwith "shift must be inside reset"
  | Some p -> Delimcc.shift p fun_k;;
# let abort x = match !reset_label with
  | None -> failwith "abort must be inside reset"
  | Some p -> Delimcc.abort p x;;

(I've added that to my ~/.ocamlinit file so that it runs every time I start OCaml up. But note that the above code only works when the result types of your reset blocks are always the same throughout your whole OCaml session. For the toy examples we're working with, these result types are always int, so it's OK. But for more varied usage scenarios, you'd have to do something syntactically more complex.)

Additionally, the previous code has to be massaged a bit to have the right syntax. What you really need to write is:

let foo x = reset (fun () -> shift (fun k -> if x = 1 then k 10 else 20) + 100) in
foo 2 + 1000

That will return 1020 just like the Scheme code does. If you said ... foo 1 + 1000, you'll instead get 1110.

That was all delimited continuation operators. There's also the undelimited continuation operators, which historically were developed first. Here you don't see the same kind of variety that you do with the delimited continuation operators. Essentially, there is just one full-strength undelimited continuation operator. But there are several different syntactic forms for working with it. (Also, a language might provide handicapped continuation operators alongside, or instead of, the full-strength one. Some loser languages don't even do that much.) The historically best-known of these is expressed in Scheme as call-with-current-continuation, or call/cc for short. But we think it's a bit easier to instead use the variant let/cc. The following code is equivalent, and shows how these two forms relate to each other:

(let/cc k ...)

(call/cc (lambda (k) ...))

(let/cc k ...) is a lot like (shift k ...) (or in the OCaml version, shift (fun k -> ...)), except that it doesn't need a surrounding (reset ... ) (in OCaml, reset (fun () -> ...)). For the undelimited continuation operator, the box is understood to be the whole rest of the top-level computation. If you're running a file, that's all the rest of the file that would have been executed after the syntactic hole filled by (let/cc k ...). With (shift k ...), the code that gets bound to k doesn't get executed unless you specifically invoke k; but let/cc works differently in this respect. Thus:

(+ 100 (let/cc k 1))

returns 101, whereas:

(reset (+ 100 (shift k 1)))

only returns 1. It is possible to duplicate the behavior of let/cc using reset/shift, but you have to structure your code in certain ways to do it.

You can't duplicate the behavior of reset/shift using only let/cc, but you can do it if you also make use of a mutable reference cell. So in a way delimited continuations are more powerful, and undelimited continuations are sort-of a special case. (In the OCaml code above for using delimited continuations, there is a mutable reference cell reset_label, but this is just for convenience. Oleg's library is designed for use with multiple reset blocks having different labels, and when you invoke shift you have to specify which labeled reset block you want to potentially skip the rest of. We haven't introduced that complexity into our discussion, so for convenience we worked around it in showing you how to use reset and shift in OCaml. And the mutable reference cell was only playing the role of enabling us to work around the need to explicitly specify the reset block's label.)

You may have noticed in some of our Scheme code we had the preface (require racket/control). You don't need to do anything special (in Racket) to use call/cc or let/cc, but you do need that preface to be able to use reset and shift and abort.

Examples of using these continuation operators

Here are some examples of using these different continuation operators. The continuation that gets bound to k will be in bold. I'll use an OCaml-ish syntax because that's easiest to read, but these examples don't work as-is in OCaml. The reset/shift examples need to be massaged into the form displayed above for OCaml; and the let/cc examples don't work in OCaml because that's not provided. Alternatively, you could massage all of these into Scheme syntax. You shouldn't find that hard.

  1. 100 + let/cc k. (10 + 1)
    This evaluates to 111. Nothing exotic happens here. As mentioned above, let/cc automatically feeds any normal result from its body to its surrounding continuation. You'd get the same result if you invoked the continuation explicitly, as in:
    100 + let/cc k. (k (10 + 1))

  2. 100 + let/cc k. (10 + k 1)
    k is again bound to 100 + < >. Note that after invoking k 1, the rest of the body of let/cc k. ( ... ) is discarded, so the result is simply 101. See example 11, below, for contrast with shift k. ( ... ).

  3. You aren't restricted to calling a full-strength continuation function only once; nor are you restricted to calling it only inside the let/cc block. For example:

    let p = let/cc k. (1,k) in
    let y = snd p (2, ident) in
    (fst p, y)
    In the first line, we bind the continuation function (the bold code) to k and then bind the variable p to the pair of 1 and that function. In the second line, we extract the continuation function from the pair p and apply it to the argument (2, ident). That results in us discarding the rest of that computation and instead executing the following:
    let p = (2, ident) in
    let y = snd p (2, ident) in
    (fst p, y)
    which in turn results in the nested pair (2, (2, ident)). Notice how the first time through, when p's second element is a continuation, applying it to an argument is a bit like time-travel? The metaphysically impossible kind of time-travel, where you can change what happened. The second time through, p gets bound to a different pair, whose second element is the ordinary ident function.

  4. 1000 + (100 + abort 11)
    Here the box is implicit, understood to be the rest of the code. The result is just the abort value 11, because the bold code is skipped. (This will work in Scheme but not in OCaml.)

  5. 1000 + reset (100 + abort 11)
    Here the box or delimiter is explicitly specified. The bold code is skipped, but the outside code 1000 + < > is still executed, so we get 1011.

  6. 1000 + reset (100 + shift k. (10 + 1))
    Equivalent to preceding. We bind the bold code to k but then never apply k, so the value 10 + 1 is supplied directly to the outside code 1000 + < >, resulting in 1011. (Contrast example 1.)

  7. 1000 + reset (100 + shift k. (k (10 + 1)))
    Here we do invoke the captured continuation, so what gets passed to the outside code 1000 + < > is k (10 + 1), that is, (100 + (10 + 1)). Result is 1111. In general, if the last thing that happens inside a shift k. ( ... ) body is that k is applied to an argument, then we do continue running the bold code between shift k. ( ... ) and the edge of the reset box.

  8. 1000 + reset (100 + shift k. (10 + k 1))
    This also results in 1111, but via a different path than the preceding. First, note that k is bound to 100 + < >. So k 1 is 101. Then 10 + k 1 is 10 + 101. Then we exit the body of shift k. ( ... ), without invoking k again, so we don't add 100 any more times. Thus we pass 10 + 101 to the outside code 1000 + < >. So the result is 1000 + (10 + 101) or 1111. (Whereas in the preceding example, the result was 1000 + (100 + 11). The order in which 1 is added to 10 and 100 is different. If we used a non-commutative operation instead of +, the results of these two examples would be different from each other.)

  9. 1000 + reset (100 + shift k. (k)) 1
    Here k is bound to 100 + < >. That function k is what's returned by the shift k. ( ... ) block, and since k isn't invoked (applied) when doing so, the rest of the bold reset block is skipped (for now). So we resume the outside code 1000 + < > 1, with what fills the gap < > being the function that was bound to k. Thus this is equivalent to 1000 + (fun x -> 100 + x) 1 or 1000 + 101 or 1101.

  10. 1000 + reset (100 + shift k. (k (k 1)))
    Here k is bound to 100 + < >. Thus k 1 is 101. Now there are two ways to think about what happens next. (Both are valid.) One way to think is that since the shift block ends with an additional outermost application of k, then as described in example 7 above, we continue through the bold code with the value k 1 or 101. Thus we get 100 + 101, and then we continue with the outermost code 1000 + < >, getting 1000 + (100 + 101), or 1201. The other way to think is that since k is 100 + < >, and k 1 is 101, then k (k 1) is 201. Now we leave the shift block without executing the bold code a third time (we've already taken account of the two applications of k), resuming with the outside code 1000 + < >, thereby getting 1000 + 201 as before.

  11. Here's another comparison of let/cc to shift. Recall example 2 above was:

    100 + let/cc k. (10 + k 1)
    which evaluated to 101. The parallel code where we instead capture the continuation using shift k. ( ... ) would look like this:
    reset (100 + shift k. (10 + k 1))
    But this evaluates differently, as we saw in example 8. In the let/cc example, k is bound to the rest of the computation including its termination, so after executing k 1 we never come back and finish with 10 + < >. A let/cc-bound k never returns to the context where it was invoked. Whereas the shift-bound k only includes up to the edge of the reset box --- here, the rest of the computation, but not including its termination. So after k 1, if there is still code inside the body of shift, as there is here, we continue executing it. Thus the shift code evaluates to 111 not to 101.

    Thus code using let/cc can't be straightforwardly translated into code using shift. It can be translated, but the algorithm will be more complex.

Some call/cc (or let/cc) exercises from The Seasoned Schemer

Here are a series of examples from The Seasoned Schemer, which we recommended at the start of term. It's not necessary to have the book to follow the exercises, though if you do have it, its walkthroughs will give you useful assistance.

For reminders about Scheme syntax, see here, and here and here. Other resources are on our Learning Scheme page.

Most of the examples assume the following preface:

#lang racket

(define (atom? x)
  (and (not (pair? x)) (not (null? x))))

Now try to figure out what this function does:

(define alpha
  (lambda (a lst)
    (let/cc k ; now what will happen when k is called?
      (letrec ([aux (lambda (l)
                      (cond
                        [(null? l) '()]
                        [(eq? (car l) a) (k (aux (cdr l)))]
                        [else (cons (car l) (aux (cdr l)))]))])
        (aux lst)))))

Here is the answer, but try to figure it out for yourself.

Next, try to figure out what this function does:

(define beta
  (lambda (lst)
    (let/cc k ; now what will happen when k is called?
      (letrec ([aux (lambda (l)
                      (cond
                        [(null? l) '()]
                        [(atom? (car l)) (k (car l))]
                        [else (begin
                                ; what will the value of the next line be? why is it ignored?
                                (aux (car l))
                                (aux (cdr l)))]))])
        (aux lst)))))

Here is the answer, but try to figure it out for yourself.

Next, try to figure out what this function does:

(define gamma
  (lambda (a lst)
    (letrec ([aux (lambda (l k)
                    (cond
                      [(null? l) (k 'notfound)]
                      [(eq? (car l) a) (cdr l)]
                      [(atom? (car l)) (cons (car l) (aux (cdr l) k))]
                      [else
                       ; what happens when (car l) exists but isn't an atom?
                       (let ([car2 (let/cc k2 ; now what will happen when k2 is called?
                                     (aux (car l) k2))])
                         (cond
                           ; when will the following condition be met? what happens then?
                           [(eq? car2 'notfound) (cons (car l) (aux (cdr l) k))]
                           [else (cons car2 (cdr l))]))]))]
             [lst2 (let/cc k1 ; now what will happen when k1 is called?
                     (aux lst k1))])
      (cond
        ; when will the following condition be met?
        [(eq? lst2 'notfound) lst]
        [else lst2]))))

Here is the answer, but try to figure it out for yourself.

Here is the hardest example. Try to figure out what this function does:

(define delta
  (letrec ([yield (lambda (x) x)]
           [resume (lambda (x) x)]
           [walk (lambda (l)
                   (cond
                     ; is this the only case where walk returns a non-atom?
                     [(null? l) '()]
                     [(atom? (car l)) (begin
                                        (let/cc k2 (begin
                                          (set! resume k2) ; now what will happen when resume is called?
                                          ; when the next line is executed, what will yield be bound to?
                                          (yield (car l))))
                                        ; when will the next line be executed?
                                        (walk (cdr l)))]
                     [else (begin
                             ; what will the value of the next line be? why is it ignored?
                             (walk (car l))
                             (walk (cdr l)))]))]
           [next (lambda () ; next is a thunk
                   (let/cc k3 (begin
                     (set! yield k3) ; now what will happen when yield is called?
                     ; when the next line is executed, what will resume be bound to?
                     (resume 'blah))))]
           [check (lambda (prev)
                    (let ([n (next)])
                      (cond
                        [(eq? n prev) #t]
                        [(atom? n) (check n)]
                        ; when will n fail to be an atom?
                        [else #f])))])
    (lambda (lst)
      (let ([fst (let/cc k1 (begin
                   (set! yield k1) ; now what will happen when yield is called?
                   (walk lst)
                   ; when will the next line be executed?
                   (yield '())))])
        (cond
          [(atom? fst) (check fst)]
          ; when will fst fail to be an atom?
          [else #f])
        ))))

Here is the answer, but again, first try to figure it out for yourself.