Difference between revisions of "Continuation"

From HaskellWiki
Jump to navigation Jump to search
m (Usng hand-made term ``non-continuation argument'')
m (Fix a 404.)
(24 intermediate revisions by 10 users not shown)
Line 9: Line 9:
 
==== Imperative metaphors ====
 
==== Imperative metaphors ====
   
* “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 [http://en.wikipedia.org/wiki/Continuation Continuation]).
+
* 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 [http://en.wikipedia.org/wiki/Continuation Continuation]).
* “At its heart, <code>call/cc</code> is something like the <code>goto</code> instruction (or rather, like a label for a <code>goto</code> instruction); but a Grand High Exalted <code>goto</code> instruction... The point about <code>call/cc</code> is that it is not a ''static'' (lexical) <code>goto</code> instruction but a ''dynamic'' one“ (David Madore's [http://www.madore.org/~david/computers/callcc.html#sec_intro A page about <code>call/cc</code>])
+
* At its heart, <code>call/cc</code> is something like the <code>goto</code> instruction (or rather, like a label for a <code>goto</code> instruction); but a Grand High Exalted <code>goto</code> instruction... The point about <code>call/cc</code> is that it is not a ''static'' (lexical) <code>goto</code> instruction but a ''dynamic'' one (David Madore's [http://www.madore.org/~david/computers/callcc.html#sec_intro A page about <code>call/cc</code>])
   
 
==== Functional metaphors ====
 
==== Functional metaphors ====
   
* “Continuations represent the future of a computation, as a function from an intermediate result to the final result“ ([http://www.nomaware.com/monads/html/contmonad.html#motivation Continuation monad] section in Jeff Newbern's All About Monads)
+
* Continuations represent the future of a computation, as a function from an intermediate result to the final result ([http://www.haskell.org/haskellwiki/All_About_Monads#The_Continuation_monad] section in Jeff Newbern's All About Monads)
* “The idea behind CPS is to pass around as a function argument what to do next“ ([http://www.isi.edu/~hdaume/htut/ Yet Another Haskell Tutorial] written by Hal Daume III, 4.6 Continuation Passing Style, pp 53-56))
+
* The idea behind CPS is to pass around as a function argument what to do next ([http://darcs.haskell.org/yaht/yaht.pdf Yet Another Haskell Tutorial] written by Hal Daume III, 4.6 Continuation Passing Style, pp 53-56). [http://en.wikibooks.org/wiki/Haskell/YAHT/Type_basics#Continuation_Passing_Style It can be read also in wikified format].
  +
* Rather than return the result of a function, pass one or more [[Higher order function | 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.
   
=== Links ===
+
=== External links ===
   
  +
* [http://en.wikibooks.org/wiki/Haskell/Continuation_passing_style The appropriate section of Haskell: Functional Programming with Types].
 
* Wikipedia's [http://en.wikipedia.org/wiki/Continuation Continuation] is a surprisingly good introductory material on this topic. See also [http://en.wikipedia.org/wiki/Continuation-passing_style Continuation-passing style].
 
* Wikipedia's [http://en.wikipedia.org/wiki/Continuation Continuation] is a surprisingly good introductory material on this topic. See also [http://en.wikipedia.org/wiki/Continuation-passing_style Continuation-passing style].
* [http://www.isi.edu/~hdaume/htut/ Yet Another Haskell Tutorial] written by Hal Daume III contains a section on continuation passing style (4.6 Continuation Passing Style, pp 53-56)
+
* [http://darcs.haskell.org/yaht/yaht.pdf Yet Another Haskell Tutorial] written by Hal Daume III contains a section on continuation passing style (4.6 Continuation Passing Style, pp 53-56). [http://en.wikibooks.org/wiki/Haskell/YAHT/Type_basics#Continuation_Passing_Style It can be read also in wikified format], thanks to Eric Kow.
* HaWiki has a page on [http://haskell.cs.yale.edu/hawiki/ContinuationPassingStyle ContinuationPassingStyle], and some related pages linked from there, too.
 
 
* David Madore's [http://www.madore.org/~david/computers/callcc.html A page about <code>call/cc</code>] describes the concept, and his [http://www.madore.org/~david/programs/unlambda/ The Unlambda Programming Language] page shows how he implemented this construct in an esoteric functional programming language.
 
* David Madore's [http://www.madore.org/~david/computers/callcc.html A page about <code>call/cc</code>] describes the concept, and his [http://www.madore.org/~david/programs/unlambda/ The Unlambda Programming Language] page shows how he implemented this construct in an esoteric functional programming language.
  +
* [http://www.defmacro.org/ramblings/fp.html#part_9 Continuations] section of article [http://www.defmacro.org/ramblings/fp.html Functional Programming For The Rest of Us], an introductory material to functional programming.
  +
* [http://okmij.org/ftp/Computation/Continuations.html Continuations and delimited control]
   
 
== Examples ==
 
== Examples ==
Line 28: Line 31:
 
=== Citing haskellized Scheme examples from Wikipedia ===
 
=== Citing haskellized Scheme examples from Wikipedia ===
   
Quoting Wikipedia's [http://en.wikipedia.org/wiki/Continuation Continuation#Examples], but Scheme examples are translated to Haskell, and some straightforward modifications are made.
+
Quoting the Scheme examples (with their explanatory texts) from Wikipedia's [http://en.wikipedia.org/wiki/Continuation-passing_style#Examples 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 <hask>fac</hask> instead of <code>factorial</code>).
   
 
In the Haskell programming language, the simplest of direct-style functions is the identity function:
 
In the Haskell programming language, the simplest of direct-style functions is the identity function:
Line 43: Line 46:
 
idCPS a ret = ret a
 
idCPS a ret = ret a
 
</haskell>
 
</haskell>
where ''ret'' is the continuation argument (often also called ''k''). A further comparison of direct and CPS style is below.
+
where <hask>ret</hask> is the continuation argument (often also called <hask>k</hask>). A further comparison of direct and CPS style is below.
 
{|
 
{|
 
!<center>Direct style</center>!!<center>Continuation passing style</center>
 
!<center>Direct style</center>!!<center>Continuation passing style</center>
Line 85: Line 88:
 
|}
 
|}
   
The translations shown above show that CPS is a global transformation; the direct-style factorial, <code>fac</code> takes, as might be expected, a single argument. The CPS factorial, <code>facCPS</code> 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.
+
The translations shown above show that CPS is a global transformation; the direct-style factorial, <hask>fac</hask> takes, as might be expected, a single argument. The CPS factorial, <hask>facCPS</hask> 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, <code>mysqrt</code> calls <code>sqrt</code> without a continuation &mdash; here <code>sqrt</code> is considered a primitive [http://en.wikipedia.org/wiki/Operator_%28programming%29 operator]; that is, it is assumed that <code>sqrt</code> 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 [http://en.wikipedia.org/wiki/Big_O_notation O(1) operation] will be considered primitive.
+
As an exception, <hask>mysqrt</hask> calls <hask>sqrt</hask> without a continuation &mdash; here <hask>sqrt</hask> is considered a primitive [http://en.wikipedia.org/wiki/Operator_%28programming%29 operator]; that is, it is assumed that <hask>sqrt</hask> 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 [http://en.wikipedia.org/wiki/Big_O_notation O(1) operation] will be considered primitive.
   
 
The quotation ends here.
 
The quotation ends here.
  +
  +
=== Intermediate structures ===
  +
  +
The function <hask>Foreign.C.String.withCString</hask> 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 <hask>withCString :: String -> (CString -> IO a) -> IO a</hask>.
  +
This looks like continuation and the functions from continuation monad can be used,
  +
e.g. for allocation of a whole array of pointers:
  +
<haskell>
  +
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)
  +
</haskell>
  +
However, the right associativity of <hask>mapM</hask> leads to inefficiencies here.
  +
  +
See:
  +
* Cale Gibbard in Haskell-Cafe on [http://www.haskell.org/pipermail/haskell-cafe/2008-February/038963.html A handy little consequence of the Cont monad]
   
 
=== More general examples ===
 
=== More general examples ===
   
 
Maybe it is confusing, that
 
Maybe it is confusing, that
* the type of the (non-continuation) argument of the discussed functions (<code>idCPS</code>, <code>mysqrtCPS</code>, <code>facCPS</code>)
+
* the type of the (non-continuation) argument of the discussed functions (<hask>idCPS</hask>, <hask>mysqrtCPS</hask>, <hask>facCPS</hask>)
 
* and the type of the argument of the continuations
 
* 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:
 
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:
Line 104: Line 130:
 
newSentenceCPS c k = k (elem c ".?!")
 
newSentenceCPS c k = k (elem c ".?!")
 
</haskell>
 
</haskell>
but this is a rather uninteresing example. Let us see another one that uses at least recursion:
+
but this is a rather uninteresting example. Let us see another one that uses at least recursion:
 
<haskell>
 
<haskell>
 
mylength :: [a] -> Integer
 
mylength :: [a] -> Integer
Line 121: Line 147:
 
</haskell>
 
</haskell>
   
You can dowload the Haskell source code (the original examples plus the new ones): [[Media:Continuation.hs|Continuation.hs]].
+
You can download the Haskell source code (the original examples plus the new ones): [[Media:Continuation.hs|Continuation.hs]].
   
 
== Continuation monad ==
 
== Continuation monad ==
   
* Jeff Newbern's [http://www.nomaware.com/monads/html/index.html All About Monads] contains a [http://www.nomaware.com/monads/html/contmonad.html section] on it.
+
* Jeff Newbern's [http://www.haskell.org/haskellwiki/All_About_Monads All About Monads] contains a [http://www.haskell.org/haskellwiki/All_About_Monads#The_Continuation_monad section] on it.
* [http://haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Cont.html Control.Monad.Cont] is contained by Haskell Hierarchical Libraries.
+
* [http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-Cont.html Control.Monad.Cont] is contained by Haskell Hierarchical Libraries.
  +
  +
== Delimited continuation ==
  +
  +
* [[Library/CC-delcont]]
  +
* [http://okmij.org/ftp/Computation/Continuations.html#zipper Generic Zipper and its applications], writing that "[[Zipper]] can be viewed as a [[Library/CC-delcont|delimited continuation]] reified as a data structure" (links added).
  +
  +
== Linguistics ==
  +
  +
Chris Barker: [http://www.cs.bham.ac.uk/~hxt/cw04/barker.pdf Continuations in Natural Language]
  +
  +
== Applications ==
  +
  +
;[http://okmij.org/ftp/Computation/Continuations.html#zipper-fs ZipperFS]
  +
:Oleg Kiselyov's [[zipper]]-based [[Libraries and tools/Operating system|file server/OS]] where threading and exceptions are all realized via [[Library/CC-delcont|delimited continuation]]s.
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]
  +
[[Category:Glossary]]

Revision as of 06:29, 12 April 2012

General or introductory materials

Powerful metaphors, images

Here is a collection of short descriptions, analogies or metaphors, that illustrate this difficult concept, or an aspect of it.

Imperative metaphors

  • 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 the goto instruction (or rather, like a label for a goto instruction); but a Grand High Exalted goto instruction... The point about call/cc is that it is not a static (lexical) goto instruction but a dynamic one (David Madore's A page about call/cc)

Functional metaphors

  • 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 be read also 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

Examples

Citing haskellized Scheme examples from Wikipedia

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.

Direct style
Continuation passing style
 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

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:

More general examples

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.

Continuation monad

Delimited continuation

Linguistics

Chris Barker: Continuations in Natural Language

Applications

ZipperFS
Oleg Kiselyov's zipper-based file server/OS where threading and exceptions are all realized via delimited continuations.