updated
authorjim <jim@web>
Thu, 30 Apr 2015 14:28:00 +0000 (10:28 -0400)
committerLinux User <ikiwiki@localhost.members.linode.com>
Thu, 30 Apr 2015 14:28:00 +0000 (10:28 -0400)
topics/week13_control_operators.mdwn

index 1ad9dd0..325c2a2 100644 (file)
-* [Example of an not-fully-immersive game](http://www.i-mockery.com/minimocks/50arcadecabinets/star-wars-arcade.gif)
-* [A more immersive game](http://upload.wikimedia.org/wikipedia/commons/7/78/AC89-0437-20_a.jpeg)
+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:
 
 
+[[/images/star-wars-arcade.gif]]
 
 
-3.     `callcc` was originally introduced in Scheme. There it's written `call/cc` and is an abbreviation of `call-with-current-continuation`. Instead of the somewhat bulky form:
+The second are more immersive games with VR goggles and gloves:
 
 
-               (call/cc (lambda (k) ...))
+[[/images/virtual-reality.jpg]]
 
 
-       I prefer instead to use the lighter, and equivalent, shorthand:
+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.
 
 
-               (let/cc k ...)
+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:
 
 
-Callcc/letcc examples
----------------------
+    let x = cell 0 in
+    ... get x ...
+    ... put 1 into x ...
 
 
-First, here are two examples in Scheme:
+With implicit mutation operators in the language, it looks instead like this:
 
 
-       (+ 100 (let/cc k (+ 10 1)))
-              |-----------------|
+    var x = 0 in
+    ... x ...
+    ... x := 1 ...
 
 
-This binds the continuation `outk` of the underlined expression to `k`, then computes `(+ 10 1)` and delivers that to `outk` in the normal way (not through `k`). No unusual behavior. It evaluates to `111`.
+The first two lines aren't very different from what we'd have without mutation:
 
 
-What if we do instead:
+    let x = 0 in
+    ... x ...
 
 
-       (+ 100 (let/cc k (+ 10 (k 1))))
-              |---------------------|
+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`. 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. Then 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.
 
 
-This time, during the evaluation of `(+ 10 (k 1))`, we supply `1` to `k`. So then the local continuation, which delivers the value up to `(+ 10 [_])` and so on, is discarded. Instead `1` gets supplied to the outer continuation in place when `let/cc` was invoked. That will be `(+ 100 [_])`. When `(+ 100 1)` is evaluated, there's no more of the computation left to evaluate. So the answer here is `101`.
+Turning to continuations, so far we've seen how to explicitly manipulate them, as in:
 
 
-You are not restricted to calling a bound continuation only once, nor are you restricted to calling it only inside of the `call/cc` (or `let/cc`) block. For example, you can do this:
+    let rec tc (xs : char list) (k : char list -> char list) =
+      ... tc xs' (fun tail -> ... k ... tail) in
+    tc some_list identity
 
 
-       (let ([p (let/cc k (cons 1 k))])
-         (cons (car p) ((cdr p) (cons 2 (lambda (x) x)))))
-       ; evaluates to '(2 2 . #<procedure>)
+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 happens here? First, we capture the continuation where `p` is about to be assigned a value. Inside the `let/cc` block, we create a pair consisting of `1` and the captured continuation. This pair is bound to p. We then proceed to extract the components of the pair. The head (`car`) goes into the start of a tuple we're building up. To get the next piece of the tuple, we extract the second component of `p` (this is the bound continuation `k`) and we apply it to a pair consisting of `2` and the identity function. Supplying arguments to `k` takes us back to the point where `p` is about to be assigned a value. The tuple we had formerly been building, starting with `1`, will no longer be accessible because we didn't bring along with us any way to refer to it, and we'll never get back to the context where we supplied an argument to `k`. Now `p` gets assigned not the result of `(let/cc k (cons 1 k))` again, but instead, the new pair that we provided: `'(2 . #<identity procedure>)`. Again we proceed to build up a tuple: we take the first element `2`, then we take the second element (now the identity function), and feed it a pair `'(2 . #<identity procedure>)`, and since it's an argument to the identity procedure that's also the result. So our final result is a nested pair, whose first element is `2` and whose second element is the pair `'(2 . #<identity procedure>)`. Racket displays this nested pair like this:
+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.
 
 
-       '(2 2 . #<procedure>)
+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.
 
 
-Some callcc/letcc exercises
----------------------------
-
-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](/assignment8/) and [here](/week1/) and [here](/translating_between_ocaml_scheme_and_haskell). 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](/hints/cps_hint_1), but try to figure it out for yourself.
+The next issue is whether the continuations are _delimited_ or not. In [[our discussion of aborts|week13_coroutines_exceptions_and_aborts#index3h2]], 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:
 
 
-Next, try to figure out what this function does:
+    initial outside code
+    +---reset--------------------+
+    | initial inside code        |
+    | shift k ( ... )            |
+    | remaining inside code      |
+    +---end----------------------+
+    remaining outside code
 
 
-       (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](/hints/cps_hint_2), but try to figure it out for yourself.
-
-Next, try to figure out what this function does:
+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 1) 1000))
+
+That shows you how `abort` can be expressed in terms of `shift`. 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 1 + 1000
+
+However, OCaml doesn't have any continuation operators in its standard deployment. If you [[installed Oleg's delimcc library|/rosetta3/#delimcc]], you can use the previous code after first doing this:
+
+    # #directory "+../delimcc";;
+    # #load "delimcc.cma";;
+    # let prompt = ref None;;
+    # let reset body = let p = Delimcc.new_prompt () in begin prompt := Some p; Delimcc.push_prompt p body end;;
+    # let shift fun_k = match !prompt with None -> failwith "shift must be inside reset" | Some p -> Delimcc.shift p fun_k;;
+
+Also, 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 1 + 1000
+
+That will return `1110` just like the Scheme code does. If you said `... foo 2 + 1000`, you'll instead get `1020`.
+
+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 (+ 10 (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. In order to duplicate the behavior of `reset`/`shift` using `let/cc`, you need to also make use of a mutable reference cell. So in that sense 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, but this is just for convenience. Oleg's library is designed for use with _multiple_ reset blocks having different labels, then 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.)
+
+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.  <pre><b>100 + </b>let/cc k (10 + 1)</pre>
+    This evaluates to `111`. Nothing exotic happens here.
+
+2.  <pre><b>100 + </b>let/cc k (10 + k 1)</pre>
+    This evaluates to `101`; `(+ 100 (let/cc k (+ 10 (k 1))))` is the same as `(reset (+ 100 (shift k (k 1))))`.
+
+3.  <pre><b>let p = </b>let/cc k (1,k) <b>in
+    let y = snd p (2, ident) in
+    (fst p, y)</b></pre>
+    In the second line, we extract the continuation function (the bold part of the previous code) from the pair `p` and apply it to the argument `(2, ident)`. That results in the following code being run:
+    <pre><b>let p = </b>(2, ident) <b>in
+    let y = snd p (2, ident) in
+    (fst p, y)</b></pre>
+    which in turn results in the nested pair `(2, (2, ident))`.
+
+4.  <pre><b>1000 + (100 + </b>abort 11<b>)</b></pre>
+    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.
+
+5.  <pre>1000 + reset <b>(100 + </b>abort 11<b>)</b></pre>
+    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.  <pre>1000 + reset <b>(100 + </b>shift k (10 + 1)<b>)</b></pre>
+    Equivalent to preceding; results in `1011`.
+
+7.  <pre>1000 + reset <b>(100 + </b>shift k (k (10 + 1))<b>)</b></pre>
+    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`.
+
+8.  <pre>1000 + reset <b>(100 + </b>shift k (10 + k 1)<b>)</b></pre>
+    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 anymore add `100`. 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 the operations are performed is different. If we used a non-commutative operation instead of `+`, the results of these two examples would be different from each other.)
+
+9.  <pre>1000 + reset <b>(100 + </b>shift k (k)<b>)</b> 1</pre>
+    Here `k` is bound to `100 + < >`. That's 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. <pre>1000 + reset <b>(100 + </b>shift k (k (k 1))<b>)</b></pre>
+    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`, 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.
 
 
-       (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](/hints/cps_hint_3), 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](/hints/cps_hint_4), but again, first try to figure it out for yourself.
-
-
-Delimited control operators
-===========================
-
-Here again is the CPS transform for `callcc`:
-
-       [callcc (\k. body)] = \outk. (\k. [body] outk) (\v localk. outk v)
-
-`callcc` is what's known as an *undelimited control operator*. That is, the continuations `outk` that get bound into our `k`s include all the code from the `call/cc ...` out to *and including* the end of the program. Calling such a continuation will never return any value to the call site.
-
-(See the technique employed in the `delta` example above, with the `(begin (let/cc k2 ...) ...)`, for a work-around. Also. if you've got a copy of *The Seasoned Schemer*, see the comparison of let/cc vs. "collector-using" (that is, partly CPS) functions at pp. 155-164.)
-
-Often times it's more useful to use a different pattern, where we instead capture only the code from the invocation of our control operator out to a certain boundary, not including the end of the program. These are called *delimited control operators*. A variety of these have been formulated. The most well-behaved from where we're coming from is the pair `reset` and `shift`. `reset` sets the boundary, and `shift` binds the continuation from the position where it's invoked out to that boundary.
-
-It works like this:
-
-       (1) outer code
-       ------- reset -------
-       | (2)               |
-       | +----shift k ---+ |
-       | | (3)           | |
-       | |               | |
-       | |               | |
-       | +---------------+ |
-       | (4)               |
-       +-------------------+
-       (5) more outer code
-
-First, the code in position (1) runs. Ignore position (2) for the moment. When we hit the `shift k`, the continuation between the `shift` and the `reset` will be captured and bound to `k`. Then the code in position (3) will run, with `k` so bound. The code in position (4) will never run, unless it's invoked through `k`. If the code in position (3) just ends with a regular value, and doesn't apply `k`, then the value returned by (3) is passed to (5) and the computation continues.
-
-So it's as though the middle box---the (2) and (4) region---is by default not evaluated. This code is instead bound to `k`, and it's up to other code whether and when to apply `k` to any argument. If `k` is applied to an argument, then what happens? Well it will be as if that were the argument supplied by (3) only now that argument does go to the code (4) syntactically enclosing (3). When (4) is finished, that value also goes to (5) (just as (3)'s value did when it ended with a regular value). `k` can be applied repeatedly, and every time the computation will traverse that same path from (4) into (5).
-
-I set (2) aside a moment ago. The story we just told is a bit too simple because the code in (2) needs to be evaluated because some of it may be relied on in (3).
-
-For instance, in Scheme this:
-
-       (require racket/control)
-       
-       (reset
-        (let ([x 1])
-          (+ 10 (shift k x))))
-
-will return 1. The `(let ([x 1]) ...` part is evaluated, but the `(+ 10 ...` part is not.
-
-Notice we had to preface the Scheme code with `(require racket/control)`. You don't have to do anything special to use `call/cc` or `let/cc`; but to use the other control operators we'll discuss you do have to include that preface in Racket.
-
-This pattern should look somewhat familiar. Recall from our discussion of aborts, and repeated at the top of this page:
-
-       let foo x =
-       +---try begin----------------+
-       |       (if x = 1 then 10    |
-       |       else abort 20        |
-       |       ) + 100              |
-       +---end----------------------+
-       in (foo 2) + 1000;;
-
-The box is working like a reset. The `abort` is implemented with a `shift`. Earlier, we refactored our code into a more CPS form:
-
-       let x = 2
-       in let snapshot = fun box ->
-           let foo_result = box
-           in (foo_result) + 1000
-       in let continue_normally = fun from_value ->
-           let value = from_value + 100
-           in snapshot value
-       in
-           if x = 1 then continue_normally 10
-           else snapshot 20;;
-
-`snapshot` here corresponds to the code outside the `reset`. `continue_normally` is the middle block of code, between the `shift` and its surrounding `reset`. This is what gets bound to the `k` in our `shift`. The `if...` statement is inside a `shift`. Notice there that we invoke the bound continuation to "continue normally". We just invoke the outer continuation, saved in `snapshot` when we placed the `reset`, to skip the "continue normally" code and immediately abort to outside the box.
-
----
-
-Examples of shift/reset/abort
------------------------------
-
-Here are some more examples of using delimited control operators. We present each example three ways: first a Scheme formulation; then we compute the same result using CPS and the lambda evaluator; then we do the same using the Continuation monad in OCaml. (We don't demonstrate the use of Oleg's delimcc library.)
-
-
-Example 1:
-
-       ; (+ 1000 (+ 100 (abort 11))) ~~> 11
-       
-       app2 (op2 plus) (var thousand)
-         (app2 (op2 plus) (var hundred) (abort (var eleven)))
-       
-       # Continuation_monad.(run0(
-           abort 11 >>= fun i ->
-           unit (100+i) >>= fun j ->
-           unit (1000+j)));;
-       - : int = 11
-
-When no `reset` is specified, there's understood to be an implicit one surrounding the entire computation (but unlike in the case of `callcc`, you still can't capture up to *and including* the end of the computation). So it makes no difference if we say instead:
-
-       # Continuation_monad.(run0(
-           reset (
-             abort 11 >>= fun i ->
-             unit (100+i) >>= fun j ->
-             unit (1000+j))));;
-       - : int = 11
-
-
-Example 2:
-       
-       ; (+ 1000 (reset (+ 100 (abort 11)))) ~~> 1011
-       
-       app2 (op2 plus) (var thousand)
-         (reset (app2 (op2 plus) (var hundred) (abort (var eleven))))
-       
-       # Continuation_monad.(run0(
-           reset (
-             abort 11 >>= fun i ->
-             unit (100+i)
-           ) >>= fun j ->
-           unit (1000+j)));;
-       - : int = 1011
-
-Example 3:
-
-       ; (+ 1000 (reset (+ 100 (shift k (+ 10 1))))) ~~> 1011
-
-       app2 (op2 plus) (var thousand)
-         (reset (app2 (op2 plus) (var hundred)
-           (shift (\k. ((op2 plus) (var ten) (var one))))))
-
-       Continuation_monad.(
-         let v = reset (
-           let u = shift (fun k -> unit (10 + 1))
-           in u >>= fun x -> unit (100 + x)
-         ) in let w = v >>= fun x -> unit (1000 + x)
-         in run0 w);;
-       - : int = 1011
-
-Example 4:
-
-       ; (+ 1000 (reset (+ 100 (shift k (k (+ 10 1)))))) ~~> 1111
-       
-       app2 (op2 plus) (var thousand)
-         (reset (app2 (op2 plus) (var hundred)
-           (shift (\k. (app (var k) ((op2 plus) (var ten) (var one)))))))
-       
-       Continuation_monad.(
-         let v = reset (
-           let u = shift (fun k -> k (10 :: [1]))
-           in u >>= fun x -> unit (100 :: x)
-         ) in let w = v >>= fun x -> unit (1000 :: x)
-         in run0 w);;
-       - : int list = [1000; 100; 10; 1]
-
-To demonstrate the different adding order between Examples 4 and 5, we use `::` in the OCaml version instead of `+`. Here is Example 5:
-
-       ; (+ 1000 (reset (+ 100 (shift k (+ 10 (k 1)))))) ~~> 1111 but added differently
-
-       app2 (op2 plus) (var thousand)
-         (reset (app2 (op2 plus) (var hundred)
-           (shift (\k. ((op2 plus) (var ten) (app (var k) (var one)))))))
-       
-       Continuation_monad.(let v = reset (
-           let u = shift (fun k -> k [1] >>= fun x -> unit (10 :: x))
-           in u >>= fun x -> unit (100 :: x)
-         ) in let w = v >>= fun x -> unit (1000 :: x)
-         in run0  w);;
-       - : int list = [1000; 10; 100; 1]
-
-
-Example 6:
-
-       ; (+ 100 ((reset (+ 10 (shift k k))) 1)) ~~> 111
-       
-       app2 (op2 plus) (var hundred)
-         (app (reset (app2 (op2 plus) (var ten)
-           (shift (\k. (var k))))) (var one))
-       
-       (* not sure if this example can be typed as-is in OCaml... this is the best I an do at the moment... *)
-
-       # type 'x either = Left of (int -> ('x,'x either) Continuation_monad.m) | Right of int;;
-       # Continuation_monad.(let v = reset (
-           shift (fun k -> unit (Left k)) >>= fun i -> unit (Right (10+i))
-         ) in let w = v >>= fun (Left k) ->
-             k 1 >>= fun (Right i) ->
-             unit (100+i)
-         in run0 w);;
-       - : int = 111
-
-<!--
-# type either = Left of (int -> either) | Right of int;;
-# let getleft e = match e with Left lft -> lft | Right _ -> failwith "not a Left";;
-# let getright e = match e with Right rt -> rt | Left _ -> failwith "not a Right";;
-# 100 + getright (let v = reset (fun p () -> Right (10 + shift p (fun k -> Left k))) in getleft v 1);;
--->
-
-Example 7:
-
-       ; (+ 100 (reset (+ 10 (shift k (k (k 1)))))) ~~> 121
-       
-       app2 (op2 plus) (var hundred)
-         (reset (app2 (op2 plus) (var ten)
-           (shift (\k. app (var k) (app (var k) (var one))))))
-       
-       Continuation_monad.(let v = reset (
-           let u = shift (fun k -> k 1 >>= fun x -> k x)
-           in u >>= fun x -> unit (10 + x)
-         ) in let w = v >>= fun x -> unit (100 + x)
-         in run0 w)
-       - : int = 121
-
-<!--
-
-       print_endline "=== pa_monad's Continuation Tests ============";;
-
-       (1, 5 = C.(run0 (unit 1 >>= fun x -> unit (x+4))) );;
-       (2, 9 = C.(run0 (reset (unit 5 >>= fun x -> unit (x+4)))) );;
-       (3, 9 = C.(run0 (reset (abort 5 >>= fun y -> unit (y+6)) >>= fun x -> unit (x+4))) );;
-       (4, 9 = C.(run0 (reset (reset (abort 5 >>= fun y -> unit (y+6))) >>= fun x -> unit (x+4))) );;
-       (5, 27 = C.(run0 (
-                                 let c = reset(abort 5 >>= fun y -> unit (y+6))
-                                 in reset(c >>= fun v1 -> abort 7 >>= fun v2 -> unit (v2+10) ) >>= fun x -> unit (x+20))) );;
-
-       (7, 117 = C.(run0 (reset (shift (fun sk -> sk 3 >>= sk >>= fun v3 -> unit (v3+100) ) >>= fun v1 -> unit (v1+2)) >>= fun x -> unit (x+10))) );;
-
-       (8, 115 = C.(run0 (reset (shift (fun sk -> sk 3 >>= fun v3 -> unit (v3+100)) >>= fun v1 -> unit (v1+2)) >>= fun x -> unit (x+10))) );;
-
-       (12, ["a"] = C.(run0 (reset (shift (fun f -> f [] >>= fun t -> unit ("a"::t)  ) >>= fun xv -> shift (fun _ -> unit xv)))) );;
-
-
-       (0, 15 = C.(run0 (let f k = k 10 >>= fun v-> unit (v+100) in reset (callcc f >>= fun v -> unit (v+5)))) );;
-
--->