Question

I'm trying to find how call/cc is implemented. The best I've found is this Haskell snippet:

callCC f = Cont $ \k -> runCont (f (\a -> Cont $ \_ -> k a)) k

Although this is not as simple as I want due to the Cont and runCont. I've also found descriptions of what it does, although never as clear as actual code.

So how is it implemented in its simplest form? I am tagging this with Scheme and Haskell as those are two languages I prefer.

Was it helpful?

Solution

"Implementing call/cc" doesn't really make sense at the layer you're working in; if you can implement call/cc in a language, that just means it has a built-in construct at least as powerful as call/cc. At the level of the language itself, call/cc is basically a primitive control flow operator, just like some form of branching must be.

Of course, you can implement a language with call/cc in a language without it; this is because it's at a lower level. You're translating the language's constructs in a specific manner, and you arrange this translation so that you can implement call/cc; i.e., generally, continuation-passing style (although for non-portable implementation in C, you can also just copy the stack directly; I'll cover continuation-passing style in more depth later). This does not really give any great insight into call/cc itself — the insight is into the model with which you make it possible. On top of that, call/cc is just a wrapper.

Now, Haskell does not expose a notion of a continuation; it would break referential transparency, and limit possible implementation strategies. Cont is implemented in Haskell, just like every other monad, and you can think of it as a model of a language with continuations using continuation-passing style, just like the list monad models nondeterminism.

Technically, that definition of callCC does type if you just remove the applications of Cont and runCont. But that won't help you understand how it works in the context of the Cont monad, so let's look at its definition instead. (This definition isn't the one used in the current Monad Transformer Library, because all of the monads in it are built on top of their transformer versions, but it matches the snippet's use of Cont (which only works with the older version), and simplifies things dramatically.)

newtype Cont r a = Cont { runCont :: (a -> r) -> r }

OK, so Cont r a is just (a -> r) -> r, and runCont lets us get this function out of a Cont r a value. Simple enough. But what does it mean?

Cont r a is a continuation-passing computation with final result r, and result a. What does final result mean? Well, let's write the type of runCont out more explicitly:

runCont :: Cont r a -> (a -> r) -> r

So, as we can see, the "final result" is the value we get out of runCont at the end. Now, how can we build up computations with Cont? The monad instance is enlightening:

instance Monad (Cont r) where
  return a = Cont (\k -> k a)
  m >>= f = Cont (\k -> runCont m (\result -> runCont (f result) k))

Well, okay, it's enlightening if you already know what it means. The key thing is that when you write Cont (\k -> ...), k is the rest of the computation — it's expecting you to give it a value a, and will then give you the final result of the computation (of type r, remember) back, which you can then use as your own return value because your return type is r too. Whew! And when we run a Cont computation with runCont, we're simply specifying the final k — the "top level" of the computation that produces the final result.

What's this "rest of the computation" called? A continuation, because it's the continuation of the computation!

(>>=) is actually quite simple: we run the computation on the left, giving it our own rest-of-computation. This rest-of-computation just feeds the value into f, which produces its own computation. We run that computation, feeding it into the rest-of-computation that our combined action has been given. In this way, we can thread together computations in Cont:

computeFirst >>= \a ->
computeSecond >>= \b ->
return (a + b)

or, in the more familiar do notation:

do a <- computeFirst
   b <- computeSecond
   return (a + b)

We can then run these computations with runCont — most of the time, something like runCont foo id will work just fine, turning a foo with the same result and final result type into its result.

So far, so good. Now let's make things confusing.

wtf :: Cont String Int
wtf = Cont (\k -> "eek!")

aargh :: Cont String Int
aargh = do
  a <- return 1
  b <- wtf
  c <- return 2
  return (a + b + c)

What's going on here?! wtf is a Cont computation with final result String and result Int, but there's no Int in sight.

What happens when we run aargh, say with runCont aargh show — i.e., run the computation, and show its Int result as a String to produce the final result?

We get "eek!" back.

Remember how k is the "rest of the computation"? What we've done in wtf is cunningly not call it, and instead supply our own final result — which then becomes, well, final!

This is just the first thing continuations can do. Something like Cont (\k -> k 1 + k 2) runs the rest of the computation as if it returned 1, and again as if it returned 2, and adds the two final results together! Continuations basically allow expressing arbitrarily complex non-local control flow, making them as powerful as they are confusing. Indeed, continuations are so general that, in a sense, every monad is a special case of Cont. Indeed, you can think of (>>=) in general as using a kind of continuation-passing style:

(>>=) :: (Monad m) => m a -> (a -> m b) -> m b

The second argument is a continuation taking the result of the first computation and returning the rest of the computation to be run.

But I still haven't answered the question: what's going on with that callCC? Well, it calls the function you give with the current continuation. But hang on a second, isn't that what we were doing with Cont already? Yes, but compare the types:

Cont   :: ((a -> r)        -> r)        -> Cont r a
callCC :: ((a -> Cont r b) -> Cont r a) -> Cont r a

Huh. You see, the problem with Cont is that we can't sequence actions from inside of the function we pass — we're just producing an r result in a pure manner. callCC lets the continuation be accessed, passed around, and just generally be messed around with from inside Cont computations. When we have

do a <- callCC (\cc -> ...)
   foo ...

You can imagine cc being a function we can call with any value inside the function to make that the return value of callCC (\cc -> ...) computation itself. Or, of course, we could just return a value normally, but then calling callCC in the first place would be a little pointless :)

As for the mysterious b there, it's just because you can use cc foo to stand in for a computation of any type you want, since it escapes the normal control flow and, like I said, immediately uses that as the result of the entire callCC (\cc -> ...). So since it never has to actually produce a value, it can get away with returning a value of any type it wants. Sneaky!

Which brings us to the actual implementation:

callCC f = Cont (\k -> runCont (f (\a -> Cont (\_ -> k a))) k)

First, we get the entire rest of the computation, and call it k. But what's this f (\a -> Cont (\_ -> k a)) part about? Well, we know that f takes a value of type (a -> Cont r b), and that's what the lambda is — a function that takes a value to use as the result of the callCC f, and returns a Cont computation that ignores its continuation and just returns that value through k — the "rest of the computation" from the perspective of callCC f. OK, so the result of that f call is another Cont computation, which we'll need to supply a continuation to in order to run. We just pass the same continuation again since, if everything goes normally, we want whatever the computation returns to be our return value and continue on normally. (Indeed, passing another value wouldn't make sense — it's "call with current continuation", not "call with a continuation other than the one you're actually running me with".)

All in all, I hope you found this as enlightening as it is long. Continuations are very powerful, but it can take a lot of time to get an intuition for how they work. I suggest playing around with Cont (which you'll have to call cont to get things working with the current mtl) and working out how you get the results you do to get a feel for the control flow.

Recommended further reading on continuations:

OTHER TIPS

call/cc is trivial to implement. The hard part is setting up the environment where it is possible to implement.

We must first define a continuation-passing style (CPS) execution environment. In this environment, your functions (or function-like things) don't directly return values; instead, they are passed a function that represents the 'next step' in the computation - the 'continuation' - and they pass their result there. In Haskell, this looks like this:

newtype Cont r a = Cont { runCont :: (a -> r) -> r }

As you can see, a Cont monad action is really a function that takes a continuation (a -> r), passes a result a to the continuation, and gets back a final result of r, which it simply passes through to its caller (ie, a Cont monad action should tail call into the continuation). runCont just takes it out of the newtype wrapper - you could also think of it as invoking an action with some particular continuation, as in runCont someAction someContinuation.

We can then turn this into a monad:

instance Monad (Cont r) where
    return x = Cont $ \cc -> cc x
    (Cont f) (>>=) g = Cont $ \cc -> f (\r -> runCont (g r) cc)

As you can see, return just gets a continuation cc, and passes its value to the continuation. (>>=) is a bit trickier, it has to invoke f with a continuation that then invokes g, gets the action back, and then passes the outer continuation to this new action.

So given this framework, getting at the continuation is simple. We just want to invoke a function with its continuation twice. The tricky part is we need to rewrap this continuation in a new monadic action that throws out the existing continuation. So let's break it down a bit:

-- Invoke a raw continuation with a given argument, throwing away our normal 
-- continuation
gotoContinuation :: (a -> r) -> a -> Cont r x
gotoContinuation continuation argument = Cont $ \_ -> continuation argument

-- Duplicate the current continuation; wrap one up in an easy-to-use action, and
-- the other stays the normal continuation for f
callCC f = Cont $ \cc -> runCont (f (gotoContinuation cc)) cc

Simple, no?

In other languages like Scheme, the principle is the same, although it may be implemented as a compiler primitive; the reason we can do it in Haskell is because the continuation-passing was something we defined in Haskell, not at a lower level of the runtime. But the principle is the same - you need to have CPS first, and then call/cc is a trivial application of this execution model.

You've heard the Haskell side of the equation; I'll give you the Racket/Scheme one, and whichever one is most helpful to you, you can run with it.

My answer will be a lot shorter, because I think that the best source I can give you for the implementation of call/cc in a simple racket evaluator comes from Shriram Krishnamurthi's PLAI, specifically section 20. I thought about including the relevant portion of the interpreter--it's on page 205--but after trying to reformat it several times I decided that it would make more sense in its proper place on the page.

Again, I'm not trying to explain the idea behind call/cc here, just point you to a working implementation. Let me know if you have other questions.

Well, I'll provide a much shorter, Scheme-based answer, since this is tagged "scheme" too.

To understand why your attempt to implement call/cc must fail, you must understand what continuation-passing style is. Once you understand that, it's pretty simple:

  • call/cc can't be implemented in direct style.
  • It is, however, trivial to implement in continuation-passing style.

But to give a bit more information, continuation-passing style is a flow-control discipline where you forego use of a call stack in favor a calling convention where every procedure call passes an "extra" argument: a closure that the called procedure is supposed to call when it's "done" (passing the "return value" as the argument). These extra argument closures are called continuations.

Any program can be mechanically translated into continuation-passing style, by means of something called, appropriately enough, the CPS transformation. Many Scheme systems in fact work like that: the program is parsed, the CPS transformation is applied to it, and then the CPS abstract syntax tree is either interpreted or translated to object code.

This is how you'd implement call/cc in continuation-passing style (using continuation as the name of the extra argument for the continuation):

(define (call/cc-cps proc continuation)
  (proc continuation continuation))

As you should be able to see, (a) you can't implement this in direct style (the opposite of CPS), and (b) it's trivial in CPS. call/cc is just a procedure that takes another procedure as its argument and the (obligatory) continuation, and calls that procedure with the continuation both as its argument and its continuation.

Risking of being off-language I think that in Smalltalk continuations can be implemented and understood the easiest. The reason is that in Smalltalk the execution stack is formed from normal objects that can be accessed and manipulated like any other object.

To implement a simple continuation object the following two methods are necessary. In the first method we initialize the continuation by iterating over the parent (sender) frames (contexts) and copying their state (program counter, temporaries, arguments):

Continuation>>initializeFromContext: aContext
    context := aContext.
    stream := WriteStream on: (Array new: 200).
    [ context notNil ] whileTrue: [
        stream nextPut: context.
        1 to: context class instSize do: [ :index |
            stream nextPut: (context instVarAt: index) ].
        1 to: context size do: [ :index |
            stream nextPut: (context at: index) ].
        context := context sender ].
    values := stream contents

The second method is to resume the execution: First we unwind the current stack (again that is just a simple loop over the execution stack), then we restore the captured stack frames, reattach them to the current stack frame thisContext and resume the execution with the argument anObject:

Continuation>>value: anObject
    self terminate: thisContext.
    stream := values readStream.
    [ stream atEnd ] whileFalse: [
        context := stream next.
        1 to: context class instSize do: [ :index |
            context instVarAt: index put: stream next ].
        1 to: context size do: [ :index |
            context at: index put: stream next ] ]
    thisContext swapSender: values first.
    ^ anObject

With these two methods we can easily build callCC:

Continuation class>>callCC: aBlock
    ^ aBlock value: (self new initializeFromContext: thisContext sender)

The beauty of this approach is that the printed code shows everything that is needed to implement full continuations (and similarly other kinds of continuations). There is no behavior hidden in the system (VM). One can use a debugger to step through each part and observe how the execution stack is manipulated.

The code above is from the Seaside web-framework. To play with the code you might want to use a ready-made distribution and browse to the classes WAContinuation and WAContinuationTest.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top