Continuation
General or introductory materials[edit]
Helpful metaphors, images[edit]
Here is a collection of short descriptions, analogies or metaphors, that illustrate this difficult concept, or an aspect of it.
Imperative metaphors[edit]
- In computing, a continuation is a representation of the execution state of a program (for example, the call stack) at a certain point in time (Wikipedia's Continuation).
- At its heart,
call/cc
is something like thegoto
instruction (or rather, like a label for agoto
instruction); but a Grand High Exaltedgoto
instruction... The point aboutcall/cc
is that it is not a static (lexical)goto
instruction but a dynamic one (David Madore's A page aboutcall/cc
)
Functional metaphors[edit]
- Continuations represent the future of a computation, as a function from an intermediate result to the final result ([1] section in Jeff Newbern's All About Monads)
- The idea behind CPS is to pass around as a function argument what to do next (Yet Another Haskell Tutorial written by Hal Daume III, 4.6 Continuation Passing Style, pp 53-56. It can also be read in wikified format).
- Rather than return the result of a function, pass one or more Higher Order Functions to determine what to do with the result. Yes, direct sum like things (or in generally, case analysis, managing cases, alternatives) can be implemented in CPS by passing more continuations.
External links[edit]
- The appropriate section of Haskell: Functional Programming with Types.
- Wikipedia's Continuation is a surprisingly good introductory material on this topic. See also Continuation-passing style.
- Yet Another Haskell Tutorial written by Hal Daume III contains a section on continuation passing style (4.6 Continuation Passing Style, pp 53-56). It can be read also in wikified format, thanks to Eric Kow.
- David Madore's A page about
call/cc
describes the concept, and his The Unlambda Programming Language page shows how he implemented this construct in an esoteric functional programming language. - Continuations section of article Functional Programming For The Rest of Us, an introductory material to functional programming.
- Continuations and delimited control
More introductions and guides about continuations can be found here.
Examples[edit]
Citing haskellized Scheme examples from Wikipedia[edit]
Quoting the Scheme examples (with their explanatory texts) from Wikipedia's Continuation-passing style article, but Scheme examples are translated to Haskell, and some straightforward modifications are made to the explanations (e.g. replacing word Scheme with Haskell, or using abbreviated name fac
instead of factorial
).
In the Haskell programming language, the simplest of direct-style functions is the identity function:
id :: a -> a
id a = a
which in CPS becomes:
idCPS :: a -> (a -> r) -> r
idCPS a ret = ret a
where ret
is the continuation argument (often also called k
). A further comparison of direct and CPS style is below.
mysqrt :: Floating a => a -> a
mysqrt a = sqrt a
print (mysqrt 4) :: IO () |
mysqrtCPS :: a -> (a -> r) -> r
mysqrtCPS a k = k (sqrt a)
mysqrtCPS 4 print :: IO () |
mysqrt 4 + 2 :: Floating a => a |
mysqrtCPS 4 (+ 2) :: Floating a => a |
fac :: Integral a => a -> a
fac 0 = 1
fac n'@(n + 1) = n' * fac n
fac 4 + 2 :: Integral a => a |
facCPS :: a -> (a -> r) -> r
facCPS 0 k = k 1
facCPS n'@(n + 1) k = facCPS n $ \ret -> k (n' * ret)
facCPS 4 (+ 2) :: Integral a => a |
The translations shown above show that CPS is a global transformation; the direct-style factorial, fac
takes, as might be expected, a single argument. The CPS factorial, facCPS
takes two: the argument and a continuation. Any function calling a CPS-ed function must either provide a new continuation or pass its own; any calls from a CPS-ed function to a non-CPS function will use implicit continuations. Thus, to ensure the total absence of a function stack, the entire program must be in CPS.
As an exception, mysqrt
calls sqrt
without a continuation — here sqrt
is considered a primitive operator; that is, it is assumed that sqrt
will compute its result in finite time and without abusing the stack. Operations considered primitive for CPS tend to be arithmetic, constructors, accessors, or mutators; any O(1) operation will be considered primitive.
The quotation ends here.
Intermediate structures[edit]
The function Foreign.C.String.withCString
converts a Haskell string to a C string.
But it does not provide it for external use but restricts the use of the C string to a sub-procedure,
because it will cleanup the C string after its use.
It has signature withCString :: String -> (CString -> IO a) -> IO a
.
This looks like continuation and the functions from continuation monad can be used,
e.g. for allocation of a whole array of pointers:
multiCont :: [(r -> a) -> a] -> ([r] -> a) -> a
multiCont xs = runCont (mapM Cont xs)
withCStringArray0 :: [String] -> (Ptr CString -> IO a) -> IO a
withCStringArray0 strings act =
multiCont
(map withCString strings)
(\rs -> withArray0 nullPtr rs act)
However, the right associativity of mapM
leads to inefficiencies here.
See:
- Cale Gibbard in Haskell-Cafe on A handy little consequence of the Cont monad
More general examples[edit]
Maybe it is confusing, that
- the type of the (non-continuation) argument of the discussed functions (
idCPS
,mysqrtCPS
,facCPS
) - and the type of the argument of the continuations
coincide in the above examples. It is not a necessity (it does not belong to the essence of the continuation concept), so I try to figure out an example which avoids this confusing coincidence:
newSentence :: Char -> Bool
newSentence = flip elem ".?!"
newSentenceCPS :: Char -> (Bool -> r) -> r
newSentenceCPS c k = k (elem c ".?!")
but this is a rather uninteresting example. Let us see another one that uses at least recursion:
mylength :: [a] -> Integer
mylength [] = 0
mylength (_ : as) = succ (mylength as)
mylengthCPS :: [a] -> (Integer -> r) -> r
mylengthCPS [] k = k 0
mylengthCPS (_ : as) k = mylengthCPS as (k . succ)
test8 :: Integer
test8 = mylengthCPS [1..2006] id
test9 :: IO ()
test9 = mylengthCPS [1..2006] print
You can download the Haskell source code (the original examples plus the new ones): Continuation.hs.
Monads as stylised continuation-passing[edit]
After class today, a few of us were discussing the market for functional programmers. Talk turned to Clojure and Scala. A student who claims to understand monads said:
- To understand monad tutorials, you really have to understand monads first.
Priceless. The topic of today's class was mutual recursion. I think we are missing a base case here.
- Knowing and Doing: Student Wisdom on Monad Tutorials, Eugene Wallingford.
The partial application of (>>=)
to monadic values means they can be used in the traditional continuation-passing style:
m :: M T
h :: U -> M V
(>>=) :: M a -> (a -> M b) -> M b |
m' :: (T -> M b) -> M b
m' = (>>=) m
h' :: U -> (V -> M b) -> M b
h' x = (>>=) (h x)
-- |
Continuation monad[edit]
- Jeff Newbern's All About Monads contains a section on it.
- Control.Monad.Cont is contained by Haskell Hierarchical Libraries.
Cont
computations as question-answering boxes
Delimited continuation[edit]
- Library/CC-delcont
- Generic Zipper and its applications, writing that "Zipper can be viewed as a delimited continuation reified as a data structure" (links added).
Linguistics[edit]
Chris Barker: Continuations in Natural Language
Applications[edit]
- ZipperFS
- Oleg Kiselyov's zipper-based file server/OS where threading and exceptions are all realized via delimited continuations.
Blog Posts[edit]
- The Continuation Monad by Gabriel Gonzalez.