post two images
[lambda.git] / topics / _cps_and_continuation_operators.mdwn
1 [[!toc]]
2
3 CPS Transforms
4 ==============
5
6 We've already approached some tasks now by programming in **continuation-passing style.** We first did that with tuples at the start of term, and then with the v5 lists in [[week4]], and now more recently and self-consciously when discussing [aborts](/couroutines_and_aborts), 
7 and [the "abSd" task](/from_list_zippers_to_continuations). and the use of `tree_monadize` specialized to the Continuation monad, which required us to supply an initial continuation.
8
9 In our discussion of aborts, we showed how to rearrange code like this:
10
11
12         let foo x =
13         +---try begin----------------+
14         |       (if x = 1 then 10    |
15         |       else abort 20        |
16         |       ) + 100              |
17         +---end----------------------+
18         in (foo 2) + 1000;;
19
20 into a form like this:
21
22         let x = 2
23         in let snapshot = fun box ->
24             let foo_result = box
25             in (foo_result) + 1000
26         in let continue_normally = fun from_value ->
27             let value = from_value + 100
28             in snapshot value
29         in
30             if x = 1 then continue_normally 10
31             else snapshot 20;;
32
33 <!--
34 # #require "delimcc";;
35 # open Delimcc;;
36 # let reset body = let p = new_prompt () in push_prompt p (body p);;
37 # let test_cps x =
38       let snapshot = fun box ->
39           let foo_result = box
40           in (foo_result) + 1000
41       in let continue_normally = fun from_value ->
42           let value = from_value + 100
43           in snapshot value
44       in if x = 1 then continue_normally 10
45       else snapshot 20;;
46
47         let foo x =
48         +===try begin================+
49         |       (if x = 1 then 10    |
50         |       else abort 20        |
51         |       ) + 100              |
52         +===end======================+
53         in (foo 2) + 1000;;
54
55 # let test_shift x =
56     let foo x = reset(fun p () ->
57         (shift p (fun k ->
58             if x = 1 then k 10 else 20)
59         ) + 100)
60     in foo z + 1000;;
61
62 # test_cps 1;;
63 - : int = 1110
64 # test_shift 1;;
65 - : int = 1110
66 # test_cps 2;;
67 - : int = 1020
68 # test_shift 2;;
69 - : int = 1020
70 -->
71
72 How did we figure out how to rearrange that code? There are algorithms that can do this for us mechanically. These algorithms are known as **CPS transforms**, because they transform code that might not yet be in CPS form into that form.
73
74 We won't attempt to give a full CPS transform for OCaml; instead we'll just focus on the lambda calculus and a few extras, to be introduced as we proceed.
75
76 In fact there are multiple ways to do a CPS transform. Here is one:
77
78         [x]     --> x
79         [\x. M] --> \k. k (\x. [M])
80         [M N]   --> \k. [M] (\m. m [N] k)
81
82 And here is another:
83
84         [x]     --> \k. k x
85         [\x. M] --> \k. k (\x. [M])
86         [M N]   --> \k. [M] (\m. [N] (\n. m n k))
87
88 These transforms have some interesting properties. One is that---assuming we never reduce inside a lambda term, but only when redexes are present in the outermost level---the formulas generated by these transforms will always only have a single candidate redex to be reduced at any stage. In other words, the generated expressions dictate in what order the components from the original expressions will be evaluated. As it happens, the first transform above forces a *call-by-name* reduction order: assuming `M N` to be a redex, redexes inside `N` will be evaluated only after `N` has been substituted into `M`. And the second transform forces a *call-by-value* reduction order. These reduction orders will be forced no matter what the native reduction order of the interpreter is, just so long as we're only allowed to reduce redexes not underneath lambdas.
89
90 Plotkin did important early work with CPS transforms, and they are now a staple of academic computer science. (See the end of his 1975 paper [Call-by-name, call-by-value, and the lambda-calculus](http://homepages.inf.ed.ac.uk/gdp/publications/cbn_cbv_lambda.pdf).)
91
92 Here's another interesting fact about these transforms. Compare the translations for variables and applications in the call-by-value transform:
93
94         [x]     --> \k. k x
95         [M N]   --> \k. [M] (\m. [N] (\n. m n k))
96
97 to the implementations we proposed for `unit` and `bind` when developing a Continuation monads, for example [here](/list_monad_as_continuation_monad). I'll relabel some of the variable names to help the comparison:
98
99         let cont_unit x = fun k -> k x
100         let cont_bind N M = fun k -> N (fun n -> M n k)
101
102 The transform for `x` is just `cont_unit x`! And the transform for `M N` is, though not here exactly the same as `cont_bind N M`, quite reminiscent of it. (I don't yet know whether there's an easy and satisfying explanation of why these two are related as they are.) <!-- FIXME -->
103
104 Doing CPS transforms by hand is very cumbersome. (Try it.) But you can leverage our lambda evaluator to help you out. Here's how to do it. From here on out, we'll be working with and extending the call-by-value CPS transform set out above:
105
106         let var = \x (\k. k x) in
107         let lam = \x_body (\k. k (\x. x_body x)) in
108         let app = \m n. (\k. m (\m. n (\n. m n k))) in
109         ...
110
111 Then if you want to use [x], you'd write `var x`. If you want to use [\x. body], you'd write `lam (\x. BODY)`, where `BODY` is whatever [body] amounts to. If you want to use [m n], you'd write `app M N`, where M and N are whatever [m] and [n] amount to.
112
113 To play around with this, you'll also want to help yourself to some primitives already in CPS form. (You won't want to rebuild everything again from scratch.) For a unary function like `succ`, you can take its primitive CPS analogue [succ] to be `\u. u (\a k. k (succ a))` (where `succ` in this expansion is the familiar non-CPS form of `succ`). Then for example:
114
115         [succ x]
116                   = \k. [succ] (\m. [x] (\n. m n k))
117                 ~~> ...
118                 ~~> \k. k (succ x)
119
120 Or, using the lambda evaluator, that is:
121
122         ...
123         let op1 = \op. \u. u (\a k. k (op a)) in
124         app (op1 succ) (var x)
125         ~~> \k. k (succ x)
126
127 Some other handy tools: 
128
129         let app2 = \a b c. app (app a b) c in
130         let app3 = \a b c d. app (app (app a b) c) d in
131         let op2 = \op. \u. u (\a v. v (\b k. k (op a b))) in
132         let op3 = \op. \u. u (\a v. v (\b w. w (\c k. k (op a b c)))) in
133         ...
134
135 Then, for instance, [plus x y] would be rendered in the lambda evaluator as:
136
137         app2 (op2 plus) (var x) (var y)
138         ~~> \k. k (plus x y)
139
140 To finish off a CPS computation, you have to supply it with an "initial" or "outermost" continuation. (This is somewhat like "running" a monadic computation.) Usually you'll give the identity function, representing that nothing further happens to the continuation-expecting value.
141
142 If the program you're working with is already in CPS form, then some elegant and powerful computational patterns become available, as we've been seeing. But it's tedious to convert to and work in fully-explicit CPS form. Usually you'll just want to be using the power of continuations at some few points in your program. It'd be nice if we had some way to make use of those patterns without having to convert our code explicitly into CPS form.
143
144 Callcc
145 ======
146
147 Well, we can. Consider the space of lambda formulas. Consider their image under a CPS transform. There will be many well-formed lambda expressions not in that image---that is, expressions that aren't anybody's CPS transform. Some of these will be useful levers in the CPS patterns we want to make use of. We can think of them as being the CPS transforms of some new syntax in the original language. For example, the expression `callcc` is explained as a new bit of syntax having some of that otherwise unclaimed CPS real-estate. The meaning of the new syntax can be understood in terms of how the CPS transform we specify for it behaves, when the whole language is in CPS form.
148
149 I won't give the CPS transform for `callcc` itself, but instead for the complex form:
150
151         [callcc (\k. body)] = \outk. (\k. [body] outk) (\v localk. outk v)
152
153 The behavior of `callcc` is this. The whole expression `callcc (\k. body)`, call it C, is being evaluated in a context, call it E[\_]. When we convert to CPS form, the continuation of this occurrence of C will be bound to the variable `outk`. What happens then is that we bind the expression `\v localk. outk v` to the variable `k` and evaluate [body], passing through to it the existing continuation `outk`. Now if `body` is just, for example, `x`, then its CPS transform [x] will be `\j. j x` and this will accept the continuation `outk` and feed it `x`, and we'll continue on with nothing unusual occurring. If on the other hand `body` makes use of the variable `k`, what happens then? For example, suppose `body` includes `foo (k v)`. In the reduction of the CPS transform `[foo (k v)]`, `v` will be passed to `k` which as we said is now `\v localk. outk v`. The continuation of that application---what is scheduled to happen to `k v` after it's evaluated and `foo` gets access to it---will be bound next to `localk`. But notice that this `localk` is discarded. The computation goes on without it. Instead, it just continues evaluating `outk v`, where as we said `outk` is the outside continuation E[\_] of the whole `callcc (\k. body)` invocation.
154
155 So in other words, since the continuation in which `foo` was to be applied to the value of `k v` was discarded, that application never gets evaluated. We escape from that whole block of code.
156
157 It's important to understand that `callcc` binds `k` to a pipe into the continuation as still then installed. Not just to a function that performs the same computation as the context E[\_] does---that has the same normal form and extension. But rather, a pipe into E[\_] *in its continuation-playing role*. This is manifested by the fact that when `k v` finishes evaluating, that value is not delivered to `foo` for the computation to proceed. Instead, when `k v` finishes evaluating, the program will then be done. Not because of some "stop here" block attached to `k`, but rather because of what it is that `k` represents. Walking through the explanation above several times may help you understand this better.
158
159 So too will examples. We'll give some examples, and show you how to try them out in a variety of formats:
160
161 1.      using the lambda evaluator to check how the CPS transforms reduce
162
163         To do this, you can use the following helper function:
164
165                 let callcc = \k_body. \outk. (\k. (k_body k) outk) (\v localk. outk v) in
166                 ...
167
168         Used like this: [callcc (\k. body)] = `callcc (\k. BODY)`, where `BODY` is [body].
169
170 2.      using a `callcc` operation on our Continuation monad
171
172         This is implemented like this:
173
174                 let callcc body = fun outk -> body (fun v localk -> outk v) outk
175
176         <!-- GOTCHAS?? -->
177
178 -- cutting for control operators --
179
180 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:
181
182                 (call/cc (lambda (k) ...))
183
184         I prefer instead to use the lighter, and equivalent, shorthand:
185
186                 (let/cc k ...)
187
188
189 Callcc/letcc examples
190 ---------------------
191
192 First, here are two examples in Scheme:
193
194         (+ 100 (let/cc k (+ 10 1)))
195                |-----------------|
196
197 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`.
198
199 What if we do instead:
200
201         (+ 100 (let/cc k (+ 10 (k 1))))
202                |---------------------|
203
204 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`.
205
206 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:
207
208         (let ([p (let/cc k (cons 1 k))])
209           (cons (car p) ((cdr p) (cons 2 (lambda (x) x)))))
210         ; evaluates to '(2 2 . #<procedure>)
211
212 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:
213
214         '(2 2 . #<procedure>)
215
216 -- end of cut --
217
218 Ok, so now let's see how to perform these same computations via CPS.
219
220 In the lambda evaluator:
221
222         let var = \x (\k. k x) in
223         let lam = \x_body (\k. k (\x. x_body x)) in
224         let app = \m n. (\k. m (\m. n (\n. m n k))) in
225         let app2 = \a b c. app (app a b) c in
226         let app3 = \a b c d. app (app (app a b) c) d in
227         let op1 = \op. \u. u (\a k. k (op a)) in
228         let op2 = \op. \u. u (\a v. v (\b k. k (op a b))) in
229         let op3 = \op. \u. u (\a v. v (\b w. w (\c k. k (op a b c)))) in
230         let callcc = \k_body. \outk. (\k. (k_body k) outk) (\v localk. outk v) in
231
232         ; (+ 100 (let/cc k (+ 10 1))) ~~> 111
233         app2 (op2 plus) (var hundred) (callcc (\k. app2 (op2 plus) (var ten) (var one)))
234         ; evaluates to \k. k (plus hundred (plus ten one))
235
236 Next:
237
238         ; (+ 100 (let/cc k (+ 10 (k 1)))) ~~> 101
239         app2 (op2 plus) (var hundred) (callcc (\k. app2 (op2 plus) (var ten) (app (var k) (var one))))
240         ; evaluates to \k. k (plus hundred one)
241
242 We won't try to do the third example in this framework.
243
244 Finally, using the Continuation monad from our OCaml monad library. We begin:
245
246         # #use "path/to/monads.ml"
247         # module C = Continuation_monad;;
248
249 Now what we want to do is something like this:
250
251         # C.(run0 (100 + callcc (fun k -> 10 + 1)));;
252
253 `run0` is a special function in the Continuation monad that runs a value of that monad using the identity function as its initial continuation. The above expression won't type-check, for several reasons. First, we're trying to add 100 to `callcc (...)` but the latter is a `Continuation.m` value, not an `int`. So we have to do this instead:
254
255         # C.(run0 (callcc (fun k -> 10 + 1) >>= fun i -> 100 + i));;
256
257 Except that's still no good, because `10 + 1` and `100 + i` are of type `int`, but their context demands Continuation monadic values. So we have to throw in some `unit`s:
258
259         # C.(run0 (callcc (fun k -> unit (10 + 1)) >>= fun i -> unit (100 + i)));;
260         - : int = 111
261
262 This works and as you can see, delivers the same answer `111` that we got by the other methods.
263
264 Next we try:
265
266         # C.(run0 (callcc (fun k -> unit (10 + (k 1))) >>= fun i -> unit (100 + i)));;
267
268 That won't work because `k 1` doesn't have type `int`, but we're trying to add it to `10`. So we have to do instead:
269
270         # C.(run0 (callcc (fun k -> k 1 >>= fun j -> unit (10 + j)) >>= fun i -> unit (100 + i)));;
271         - : int = 101
272
273 This also works and as you can see, delivers the expected answer `101`.
274
275 The third example is more difficult to make work with the monadic library, because its types are tricky. I was able to get this to work, which uses OCaml's "polymorphic variants." These are generally more relaxed about typing. There may be a version that works with regular OCaml types, but I haven't yet been able to identify it. Here's what does work:
276
277         # C.(run0 (callcc (fun k -> unit (1,`Box k)) >>= fun (p1,`Box p2) -> p2 (2,`Box unit) >>= fun p2' -> unit (p1,p2')));;
278         - : int * (int * [ `Box of 'b -> ('a, 'b) C.m ] as 'b) as 'a =
279         (2, (2, `Box <fun>))
280
281 <!-- FIXME -->
282
283 -- cutting following section for control operators --
284
285 Some callcc/letcc exercises
286 ---------------------------
287
288 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.
289
290 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.
291
292 Most of the examples assume the following preface:
293
294         #lang racket
295
296         (define (atom? x)
297           (and (not (pair? x)) (not (null? x))))
298
299 Now try to figure out what this function does:
300
301         (define alpha
302           (lambda (a lst)
303             (let/cc k ; now what will happen when k is called?
304               (letrec ([aux (lambda (l)
305                               (cond
306                                 [(null? l) '()]
307                                 [(eq? (car l) a) (k (aux (cdr l)))]
308                                 [else (cons (car l) (aux (cdr l)))]))])
309                 (aux lst)))))
310         
311 Here is [the answer](/hints/cps_hint_1), but try to figure it out for yourself.
312
313 Next, try to figure out what this function does:
314
315         (define beta
316           (lambda (lst)
317             (let/cc k ; now what will happen when k is called?
318               (letrec ([aux (lambda (l)
319                               (cond
320                                 [(null? l) '()]
321                                 [(atom? (car l)) (k (car l))]
322                                 [else (begin
323                                         ; what will the value of the next line be? why is it ignored?
324                                         (aux (car l))
325                                         (aux (cdr l)))]))])
326                 (aux lst)))))
327
328 Here is [the answer](/hints/cps_hint_2), but try to figure it out for yourself.
329
330 Next, try to figure out what this function does:
331
332         (define gamma
333           (lambda (a lst)
334             (letrec ([aux (lambda (l k)
335                             (cond
336                               [(null? l) (k 'notfound)]
337                               [(eq? (car l) a) (cdr l)]
338                               [(atom? (car l)) (cons (car l) (aux (cdr l) k))]
339                               [else
340                                ; what happens when (car l) exists but isn't an atom?
341                                (let ([car2 (let/cc k2 ; now what will happen when k2 is called?
342                                              (aux (car l) k2))])
343                                  (cond
344                                    ; when will the following condition be met? what happens then?
345                                    [(eq? car2 'notfound) (cons (car l) (aux (cdr l) k))]
346                                    [else (cons car2 (cdr l))]))]))]
347                      [lst2 (let/cc k1 ; now what will happen when k1 is called?
348                              (aux lst k1))])
349               (cond
350                 ; when will the following condition be met?
351                 [(eq? lst2 'notfound) lst]
352                 [else lst2]))))
353
354 Here is [the answer](/hints/cps_hint_3), but try to figure it out for yourself.
355
356 Here is the hardest example. Try to figure out what this function does:
357
358         (define delta
359           (letrec ([yield (lambda (x) x)]
360                    [resume (lambda (x) x)]
361                    [walk (lambda (l)
362                            (cond
363                              ; is this the only case where walk returns a non-atom?
364                              [(null? l) '()]
365                              [(atom? (car l)) (begin
366                                                 (let/cc k2 (begin
367                                                   (set! resume k2) ; now what will happen when resume is called?
368                                                   ; when the next line is executed, what will yield be bound to?
369                                                   (yield (car l))))
370                                                 ; when will the next line be executed?
371                                                 (walk (cdr l)))]
372                              [else (begin
373                                      ; what will the value of the next line be? why is it ignored?
374                                      (walk (car l))
375                                      (walk (cdr l)))]))]
376                    [next (lambda () ; next is a thunk
377                            (let/cc k3 (begin
378                              (set! yield k3) ; now what will happen when yield is called?
379                              ; when the next line is executed, what will resume be bound to?
380                              (resume 'blah))))]
381                    [check (lambda (prev)
382                             (let ([n (next)])
383                               (cond
384                                 [(eq? n prev) #t]
385                                 [(atom? n) (check n)]
386                                 ; when will n fail to be an atom?
387                                 [else #f])))])
388             (lambda (lst)
389               (let ([fst (let/cc k1 (begin
390                            (set! yield k1) ; now what will happen when yield is called?
391                            (walk lst)
392                            ; when will the next line be executed?
393                            (yield '())))])
394                 (cond
395                   [(atom? fst) (check fst)]
396                   ; when will fst fail to be an atom?
397                   [else #f])
398                 ))))
399
400 Here is [the answer](/hints/cps_hint_4), but again, first try to figure it out for yourself.
401
402
403 Delimited control operators
404 ===========================
405
406 Here again is the CPS transform for `callcc`:
407
408         [callcc (\k. body)] = \outk. (\k. [body] outk) (\v localk. outk v)
409
410 `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.
411
412 (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.)
413
414 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.
415
416 It works like this:
417
418         (1) outer code
419         ------- reset -------
420         | (2)               |
421         | +----shift k ---+ |
422         | | (3)           | |
423         | |               | |
424         | |               | |
425         | +---------------+ |
426         | (4)               |
427         +-------------------+
428         (5) more outer code
429
430 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.
431
432 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).
433
434 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).
435
436 For instance, in Scheme this:
437
438         (require racket/control)
439         
440         (reset
441          (let ([x 1])
442            (+ 10 (shift k x))))
443
444 will return 1. The `(let ([x 1]) ...` part is evaluated, but the `(+ 10 ...` part is not.
445
446 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.
447
448 This pattern should look somewhat familiar. Recall from our discussion of aborts, and repeated at the top of this page:
449
450         let foo x =
451         +---try begin----------------+
452         |       (if x = 1 then 10    |
453         |       else abort 20        |
454         |       ) + 100              |
455         +---end----------------------+
456         in (foo 2) + 1000;;
457
458 The box is working like a reset. The `abort` is implemented with a `shift`. Earlier, we refactored our code into a more CPS form:
459
460         let x = 2
461         in let snapshot = fun box ->
462             let foo_result = box
463             in (foo_result) + 1000
464         in let continue_normally = fun from_value ->
465             let value = from_value + 100
466             in snapshot value
467         in
468             if x = 1 then continue_normally 10
469             else snapshot 20;;
470
471 `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.
472
473
474 -- end of cut --
475
476
477 Using `shift` and `reset` operators in OCaml, this would look like this:
478
479         #require "delimcc";;
480         let p = Delimcc.new_prompt ();;
481         let reset = Delimcc.push_prompt p;;
482         let shift = Delimcc.shift p;;
483         let abort = Delimcc.abort p;;
484         
485         let foo x =
486           reset(fun () ->
487             shift(fun continue ->
488                 if x = 1 then continue 10
489                 else 20
490             ) + 100
491           )
492         in foo 2 + 1000;;
493         - : int = 1020
494
495 If instead at the end we did `... foo 1 + 1000`, we'd get the result `1110`.
496
497 The above OCaml code won't work out of the box; you have to compile and install a special library that Oleg wrote. We discuss it on our [translation page](/translating_between_ocaml_scheme_and_haskell). If you can't get it working, then you can play around with `shift` and `reset` in Scheme instead. Or in the Continuation monad. Or using CPS transforms of your code, with the help of the lambda evaluator.
498
499 You can make the lambda evaluator perform the required CPS transforms with these helper functions:
500
501         let reset = \body. \outk. outk (body (\i i)) in
502         let shift = \k_body. \midk. (\k. (k_body k) (\i i)) (\a localk. localk (midk a)) in
503         let abort = \body. \midk. body (\i i) in
504         ...
505
506 You use these like so:
507
508 *       [reset body] is `reset BODY` where `BODY` is [body]
509 *       [shift k body] is `shift (\k. BODY)` where `BODY` is [body]
510 *       and [abort value] is `abort VALUE` where `VALUE` is [value]
511         
512 There are also `reset` and `shift` and `abort` operations in the Continuation monad in our OCaml [[monad library]]. You can check the code for details.
513
514
515 As we said, there are many varieties of delimited continuations. Another common pair is `prompt` and `control`. There's no difference in meaning between `prompt` and `reset`; it's just that people tend to say `reset` when talking about `shift`, and `prompt` when talking about `control`. `control` acts subtly differently from `shift`. In the uses you're likely to make as you're just learning about continuations, you won't see any difference. If you'll do more research in this vicinity, you'll soon enough learn about the differences.
516
517 (You can start by reading [the Racket docs](http://docs.racket-lang.org/reference/cont.html?q=shift&q=do#%28part._.Classical_.Control_.Operators%29).)
518
519
520 Ken Shan has done terrific work exploring the relations of `shift` and `control` and other control operators to each other.
521
522 In collecting these CPS transforms and implementing the monadic versions, we've been helped by Ken and by Oleg and by these papers:
523
524 *       Danvy and Filinski, "Representing control: a study of the CPS transformation" (1992)
525 *       Sabry, "Note on axiomatizing the semantics of control operators" (1996)
526
527
528 -- cutting some of the following for control operators --
529
530 Examples of shift/reset/abort
531 -----------------------------
532
533 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.)
534
535
536 Example 1:
537
538         ; (+ 1000 (+ 100 (abort 11))) ~~> 11
539         
540         app2 (op2 plus) (var thousand)
541           (app2 (op2 plus) (var hundred) (abort (var eleven)))
542         
543         # Continuation_monad.(run0(
544             abort 11 >>= fun i ->
545             unit (100+i) >>= fun j ->
546             unit (1000+j)));;
547         - : int = 11
548
549 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:
550
551         # Continuation_monad.(run0(
552             reset (
553               abort 11 >>= fun i ->
554               unit (100+i) >>= fun j ->
555               unit (1000+j))));;
556         - : int = 11
557
558
559 Example 2:
560         
561         ; (+ 1000 (reset (+ 100 (abort 11)))) ~~> 1011
562         
563         app2 (op2 plus) (var thousand)
564           (reset (app2 (op2 plus) (var hundred) (abort (var eleven))))
565         
566         # Continuation_monad.(run0(
567             reset (
568               abort 11 >>= fun i ->
569               unit (100+i)
570             ) >>= fun j ->
571             unit (1000+j)));;
572         - : int = 1011
573
574 Example 3:
575
576         ; (+ 1000 (reset (+ 100 (shift k (+ 10 1))))) ~~> 1011
577
578         app2 (op2 plus) (var thousand)
579           (reset (app2 (op2 plus) (var hundred)
580             (shift (\k. ((op2 plus) (var ten) (var one))))))
581
582         Continuation_monad.(
583           let v = reset (
584             let u = shift (fun k -> unit (10 + 1))
585             in u >>= fun x -> unit (100 + x)
586           ) in let w = v >>= fun x -> unit (1000 + x)
587           in run0 w);;
588         - : int = 1011
589
590 Example 4:
591
592         ; (+ 1000 (reset (+ 100 (shift k (k (+ 10 1)))))) ~~> 1111
593         
594         app2 (op2 plus) (var thousand)
595           (reset (app2 (op2 plus) (var hundred)
596             (shift (\k. (app (var k) ((op2 plus) (var ten) (var one)))))))
597         
598         Continuation_monad.(
599           let v = reset (
600             let u = shift (fun k -> k (10 :: [1]))
601             in u >>= fun x -> unit (100 :: x)
602           ) in let w = v >>= fun x -> unit (1000 :: x)
603           in run0 w);;
604         - : int list = [1000; 100; 10; 1]
605
606 To demonstrate the different adding order between Examples 4 and 5, we use `::` in the OCaml version instead of `+`. Here is Example 5:
607
608         ; (+ 1000 (reset (+ 100 (shift k (+ 10 (k 1)))))) ~~> 1111 but added differently
609
610         app2 (op2 plus) (var thousand)
611           (reset (app2 (op2 plus) (var hundred)
612             (shift (\k. ((op2 plus) (var ten) (app (var k) (var one)))))))
613         
614         Continuation_monad.(let v = reset (
615             let u = shift (fun k -> k [1] >>= fun x -> unit (10 :: x))
616             in u >>= fun x -> unit (100 :: x)
617           ) in let w = v >>= fun x -> unit (1000 :: x)
618           in run0  w);;
619         - : int list = [1000; 10; 100; 1]
620
621
622 Example 6:
623
624         ; (+ 100 ((reset (+ 10 (shift k k))) 1)) ~~> 111
625         
626         app2 (op2 plus) (var hundred)
627           (app (reset (app2 (op2 plus) (var ten)
628             (shift (\k. (var k))))) (var one))
629         
630         (* not sure if this example can be typed as-is in OCaml... this is the best I an do at the moment... *)
631
632         # type 'x either = Left of (int -> ('x,'x either) Continuation_monad.m) | Right of int;;
633         # Continuation_monad.(let v = reset (
634             shift (fun k -> unit (Left k)) >>= fun i -> unit (Right (10+i))
635           ) in let w = v >>= fun (Left k) ->
636               k 1 >>= fun (Right i) ->
637               unit (100+i)
638           in run0 w);;
639         - : int = 111
640
641 <!--
642 # type either = Left of (int -> either) | Right of int;;
643 # let getleft e = match e with Left lft -> lft | Right _ -> failwith "not a Left";;
644 # let getright e = match e with Right rt -> rt | Left _ -> failwith "not a Right";;
645 # 100 + getright (let v = reset (fun p () -> Right (10 + shift p (fun k -> Left k))) in getleft v 1);;
646 -->
647
648 Example 7:
649
650         ; (+ 100 (reset (+ 10 (shift k (k (k 1)))))) ~~> 121
651         
652         app2 (op2 plus) (var hundred)
653           (reset (app2 (op2 plus) (var ten)
654             (shift (\k. app (var k) (app (var k) (var one))))))
655         
656         Continuation_monad.(let v = reset (
657             let u = shift (fun k -> k 1 >>= fun x -> k x)
658             in u >>= fun x -> unit (10 + x)
659           ) in let w = v >>= fun x -> unit (100 + x)
660           in run0 w)
661         - : int = 121
662
663 <!--
664
665         print_endline "=== pa_monad's Continuation Tests ============";;
666
667         (1, 5 = C.(run0 (unit 1 >>= fun x -> unit (x+4))) );;
668         (2, 9 = C.(run0 (reset (unit 5 >>= fun x -> unit (x+4)))) );;
669         (3, 9 = C.(run0 (reset (abort 5 >>= fun y -> unit (y+6)) >>= fun x -> unit (x+4))) );;
670         (4, 9 = C.(run0 (reset (reset (abort 5 >>= fun y -> unit (y+6))) >>= fun x -> unit (x+4))) );;
671         (5, 27 = C.(run0 (
672                                   let c = reset(abort 5 >>= fun y -> unit (y+6))
673                                   in reset(c >>= fun v1 -> abort 7 >>= fun v2 -> unit (v2+10) ) >>= fun x -> unit (x+20))) );;
674
675         (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))) );;
676
677         (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))) );;
678
679         (12, ["a"] = C.(run0 (reset (shift (fun f -> f [] >>= fun t -> unit ("a"::t)  ) >>= fun xv -> shift (fun _ -> unit xv)))) );;
680
681
682         (0, 15 = C.(run0 (let f k = k 10 >>= fun v-> unit (v+100) in reset (callcc f >>= fun v -> unit (v+5)))) );;
683
684 -->