What is the use of Continuation Passing Style (CPS)?

Is there any real us for them? They just seem to obfuscate the code if you ask me! Can someone shine so light how Ocaml uses CPS if at all?

reference: https://en.wikipedia.org/wiki/Continuation-passing_style

3 Likes

Sometimes you can’t make a function tail-recursive by just adding an accumulator to its arguments and CPS is the easiest way to achieve getting the function tail-recursive.

2 Likes

CPS is also important for code analysis and optimization. A compiler can transform all code into CPS and then provide useful analysis and optimization capabilities. In fact, that’s what Flambda 2.0 will do.

I wrote a small (classical) example:

(* computing the length of a list, not tail-recursive *)
let rec list_length = function
  | [] -> 0
  | _::s -> 1 + list_length s (* not a tail call *)

(* tail-recursive version adding an accumulator *)
let list_length_tail l =
  let rec aux acc = function
  | [] -> acc
  | _::s -> aux (acc + 1) s
  in
  aux 0 l

type 'a binary_tree =
  | Empty
  | Node of 'a * ('a binary_tree) * ('a binary_tree)

(* computing the height of a tree, not tail-recursive *)
let rec tree_height = function
  | Empty -> 0
  | Node (_, l, r) -> 1 + max (tree_height l) (tree_height r)

(* impossible to make it tail-recursive adding an accumulator, try it... *)

(* tail-recursive version using CPS *)
let tree_height_tail t =
  let rec aux t k = match t with
    | Empty -> k 0
    | Node (_, l, r) ->
        aux l (fun lh ->
        aux r (fun rh ->
        k (1 + max lh rh)))
  in
  aux t (fun x -> x)

let _ =
  let l = [1; 2; 3; 4] in
  Format.printf "size of the list is: %d@." (list_length l);
  Format.printf "size of the list is: %d@." (list_length_tail l);
  let t = Node (1, Empty, Node(2, Node (3, Empty, Empty), Empty)) in
  Format.printf "height of the tree is: %d@." (tree_height t);
  Format.printf "height of the tree is: %d@." (tree_height_tail t)

Then, if you wonder why tail-recursive function is sometimes needed, well, it’s because if your list or tree is too big, your function will fail with a stack overflow.

EDIT: also note that getting from the non-cps version to the cps one is almost only syntactic :slight_smile:

let rec tree_height t = match t with
  | Empty -> 0
  | Node (_, l, r) -> 1 + max (tree_height l) (tree_height r)

(* add intermediate values: *)
let rec tree_height t = match t with
  | Empty -> 0
  | Node (_, l, r) ->
      let lh = tree_height l in
      let rh = tree_height r in
      1 + max lh rh

(* add a continuation to the args and before returning any value: *)
(* this is not valid OCaml *)
let rec tree_height t k = match t with
  | Empty -> k 0
  | Node (_, l, r) ->
      let lh = tree_height l in
      let rh = tree_height r in
      k (1 + max lh rh)

(* replace all intermediate `let x = f y` by `tree_height y (fun x ->` : *)
let rec tree_height t k = match t with
  | Empty -> k 0
  | Node (_, l, r) ->
      tree_height l (fun lh ->
      tree_height r (fun rh ->
      k (1 + max lh rh)))
5 Likes

To add a little more to what zapashcanon wrote: There are two big reasons why people ought to know about CPS:
(1) if you’re a compiler-wirter, you may find some analysis algorithms easier to accomplish with code in CPS. [not sure this is actually true since Felleisen&Sabry’s work, but hey, I left the field and don’t keep up …]
(2) if you’re a journeyman programmer, then CPS can be viewed as a generalization of the “technique of accumulating parameters”. Well, actually “CPS + defunctionalization”.

And (3) [there’s always three bullet-points in any presentation] once your code is in CPS, you’re ready to add various non-functional bits to it, like control operators, state (well, sure, not CPS, but S(tate)PS) nondeterminism, userland threading, etc.

So people who write code for Node.JS and don’t use those source-code transformer things, are writing in CPS, for example.

2 Likes

Nowadays NodeJS supports promises and async/await syntax directly so you don’t need a transpiler any more :slight_smile:

(* impossible to make it tail-recursive adding an accumulator, try it... *)

Here you go

(* invariant: height of original tree = max (best, depth + height t, list_max (List.map (fun (t',depth') -> depth' + height t') rem)) *)
let rec aux best t depth rem = match t with
  | Empty ->
    let best = max best depth in
    begin match rem with
      | [] -> best
      | (t,depth) :: rem -> aux best t depth rem
    end
  | Node (_,l,r) -> aux best l (depth+1) ((r,depth+1)::rem)

let height t = aux 0 t 0 []

To (again) merely add a little curlicue to zapashcanon’s work, I think his point is that to make it tail-recursive, you need to add more than one auxiliary parameter. And just figuring that stuff out, can be a little tricky. Whereas, if you’re programming in a language like ML (or Scheme) you can convert to CPS in a VERY straightforward way (his words “almost only syntactic” are very correct these days, with the lovely method of Danvy) and so you can get a version that is tail-recursive (and hence, uses constant stack space) in a straightforward manner.

SkySkimmer gives us the tail-recursive version with multiple auxiliary parameters, and I suspect that if one were to
(a) start with the original version
(b) CPS it in a tidy manner
© then apply “defunctionalization”

one could arrive at SkySkimmer’s version. But of course, that’s tedious, time-consuming, and liable to error. Just writing in CPS and letting the compiler do a somewhat-decent job, can get you most of the way to the efficiency of SkySkimmer’s version.

1 Like

you need to add more than one auxiliary parameter

You can tuple them up if you prefer.

And just figuring that stuff out, can be a little tricky

This is the important part.

Oh, inDEED! John Reynold’s groundbreaking paper “Definitional Interpreters for …” explained the technique, and it is tricky to execute it correctly. Well, sure, with time, one gets good at it, but geez, why not just let the compiler do a reasonably-adequate job by using CPS? grin

In general, the continuation passing style is used to implement arbitrary control flow constructs. Usually, it is the role of a programming language to provide us a set of such constructs, such as if/then/else, while and for, function calls and subroutines. This is the most basic set. Some languages also provide things like exceptions or co-routines (e.g., yield in python). But in general, it is the language designers choice, therefore we’re limited to whatever they thought would be sufficient.

For example, most of the language designers do not allow us to call into the middle of a function (aka co-routines) or to return to different places in the caller (partially filled with exceptions, but see conditions in Common Lisp).

To summarize, the design space is huge. But the good news is that CPS enables us to implement all this control-flow structures (and any other that we can imagine) without leaving the comfort zone of our language.

But before going any further, it’s time to actually define what is CPS and what is a continuation. A continuation is a function that is passed as an argument to the callee function and that can be used to return from the caller to the callee. Here, “to return from a function” means that the last expression of a function is a call, e.g.,

let parse_begin good_thing bad_thing = function
  | "begin" -> good_thing `Begin
  | error -> bad_thing error

Here we have two continuations good_thing and bad_thing. Both are used to return from the parse_begin function. In other words, the parse_function never ends, it just calls bad_thing or good_thing and neither is expected to return. Compare it with the direct style, e.g.,

let parse_begin = function
  | "begin" -> Ok `Begin
  | error -> Error ("expects begin, got " ^ error)

In the direct style we are using explicit tagged values so that the caller may later decide how to branch on them, while in the CPS style we’re reifying the if/then/else control structure and passing it directly to the callee, letting the callee to decide which of the branches to pursue.

The direct style might be more appealing and easier to understand, so you might wonder, why and when we should prefer the CPS style in this example. The answer is that CPS could be much more efficient than the direct style. In the direct style every time a function returns it a variant value it must allocate a new object and copy the result into its content. The allocation is slow by itself but it also incurs additional costs, since the garbage collector will need to copy or remove this created object later.

In CPS, we pass objects directly, and the continuation is just a pointer to a function and we pass values to it using an efficient calling convention (i.e., directly through a register, instead of creating an object in the heap and passing a reference to it). Therefore we came to the first justified reason to use CPS:

Use case #1. Writing performance critical code, which makes a lot of decisions based on the tagged data structures. CPS enables short-circuiting the decisions so that they are made on the callee side and not postponed till the caller.

To build a little bit more intuition for this case, it is very close to the visitor vs. if/then/else dilemma in OOP languages in which the passed visitor acts as a continuation. OOP languages, however, rarely have the tail-call optimization which is necessary for CPS to work efficiently, but they compensate it by relying on side-effects and storing the result of computation directly in the continuation.

This brings us to another feature of continuations – state. In our previous example, we assumed that the contination is stateless and is just a function that takes input and computes output (and uses uses another continuation to pass it further). However, the continuation could be a closure, so in addition to the code it may also contain some data payload. This opens an opportunity to use closures as data structures. Let’s start with the simplest example of a closure as a data structure,

module Dict : sig
  type ('a,'b) t
  val empty : ('a,'b) t
  val add : ('a,'b) t -> 'a -> 'b -> ('a,'b) t
  val get : ('a,'b) t -> 'a -> 'b
end = struct
  type ('a,'b) t = 'a -> 'b
  let empty _ = raise Not_found
  let add f k v = fun k' -> if k = k' then v else f k'
  let get f k = f k
end

In this example, we used a chain of closures to implement an associative array. The trick is that every time we add a new value we create a closure fun k' -> if k = k' then v else f k' in which k, v, and f are free and therefore are stored in the body of the closure, so that roughly it is now a data type having three fields, e.g.,

type ('a,'b) closure2 = {key : 'a; data : 'b; next : ('a,'b) closure2}

which is totally isomorphic to a normal ('a * 'b) list which we normally use to implement assoc lists.

Now we’re getting closer to the second use case - implementing recursive algorithms with constant stack space. Often, when we’re dealing with recursive data structures like trees or lists, in order to compute the result for one element, we need to get the value for all other elements, like the map being the simplest example:

let rec map f = function
 | x :: xs -> f x :: map f xs 
 | [] -> []

which says that map f (x::xs) is f x prepended to the result of map f xs. So in order to compute the result, we need to get the result for all other elements, which basically means that we need to store f x somewhere and keep it in mind until the rest is ready. The magic of recursive calls automatically gives us the place to store this intermediate information. This place is called stack and it is a scarce resource and if you will use it all, then the operating system will terminate your program. In other words, not the best place to store your data. Therefore we have to reimplement our algorithm so that the intermediate results will be stored in the heap (which is basically unlimited). The usual solution would be to use a list for that (because list is basically the stack). But in some cases, it is not really possible, especially in the cases when our data structure is complex, e.g., graph. For a particular example, in Graphlib we used continuations to dynamically make a choice between a tail-recursive (which is slower) and the non tail-recursive version (which is faster). Besides, if you ever wanted to know why in the standard library List.map is not tail-recursive by default, the answer is simple - performance. Native stack works faster than its list counterpart. So w came to the next use case:

Use case #2: For turning a stack-based recursion into a heap-based recursion.

But those are just nifty tricks, now let’s do the real stuff. An important aspect of CPS is that a called continuation should not return, but should instead call a continuation on itself, which was passed to it and so on and so on. So that a chain of computations is built. This is what is called the continuation passing style programming. Only if we will adhere to this style and chain all our computations through continuations, we will be able to ripe the most tasteful fruits like implementing our own control flow operators. However, writing the whole program in this style is too hardcore and mind blowing.

Fortunately, there is a solution. In CPS, we have a continuation usually as the last parameter, therefore our functions are having type inputs -> ('a -> 'r) -> 'r. Thus we can represent ('a -> 'r) -> 'r computation as a continuation monad

type ('a,'r') monad = ('a -> 'r) -> 'r

For which we can implement the monad interface, and now our scary CPS looks like a furry monad, which no longer scares. There is no sense, of course, of writing code in the Cont monad unless we’re going to use it to build our own control structures. And there is the call/cc operator which makes it very easy (ok just a little bit easier) to implement those. In OCaml it has a scary type though:

 val call : f:(cc:('a -> (_,'e) t) -> ('a,'e) t) -> ('a,'e) t

(recall that ('a,'e) t is actuall ('a -> 'e) -> 'e, so the actual type is

val call:(cc:('a -> ('a -> 'e) -> 'e) -> ('a -> 'e) -> 'e)) -> ('a -> 'e) -> 'e

That’s why we use abstractions, to make hard things easier to grasp :slight_smile:
So using the continuation monad (which is just a tamed CPS) we can easily implement exceptions, co-routines, non-deterministic computations, algorithms with backtracking, etc. A real-world example would be our Primus Framework which is a non-deterministic program interpreter. This interpreter brings only two new insteresting operators:

fork : unit -> unit machine
switch : pid -> pid machine

where 'a machine is the type for our non-deterministic machine. The fork operator, stores the current continuations and creates a new continuation. The switch operator will pause the current computation and will transfer the control-flow to the point where a machine with the given pid forked or switched last time. Therefore, both fork and switch will return multiple times. Both operators are implemented using call/cc. Here is a simple example, in which we run each a list of addresses each in its own fork:

let rec run = function
  | [] -> Eval.halt >>=  never_returns
  | x :: xs ->
    Machine.current () >>= fun pid ->
    Machine.fork ()    >>= fun () ->
    Machine.current () >>= fun cid ->
    if pid = cid then run xs
    else exec x >>= fun () -> Eval.halt >>= never_returns

Therefore, this is our use case #3.

Use case #3 for implementing exotic control-flow, which enables co-routines and non-deterministic computation with backtracking and other features – all for one reason, to make otherwise hard to implemented and understand algorithms easy to encode.

Finally, in languages with powerful type systems, continuations could be used for implementing variadic functions, i.e., functions which have an arbitrary number of arguments of different types, all defined by the first argument. A good example is the kfprintf function (notice, it is taking a continuation as the first argument). I don’t really have time to elaborate on them, but here is another example, in which continuations are used to build typesafe interface for SQL-like style querying language. They all use continuations underneath the hood. And here is our final use case,

Use case #4 for implementing variadic functions.

Summary

Continuations is a powerful tool that is useful in some cases (we counted at least 4), but as any other mathematical device, it should be applied only to the problems which couldn’t be solved using easier devices. For example, you can plan your travel using relativistic mechanics, but good old classical Newton’s mechanics might suit your needs much better, especially if you’re going to travel by bus :slight_smile:

24 Likes

This is close to valid OCaml, though, thanks to the binding operators recently introduced.

Using the following definitions to introduce and combine CPS style functions:

let return x = fun k -> k x
let ( let* ) x f = fun k -> x (fun y -> f y k)

We can then write:

let rec tree_height t = match t with
  | Empty -> return 0
  | Node (_, l, r) ->
      let* lh = tree_height l in
      let* rh = tree_height r in
      return (1 + max lh rh)

And (in order to have a normal non-CPS function):

let tree_height t = tree_height t (fun x -> x)
3 Likes

Markup.ml, the HTML parser, is internally implemented using CPS. This allows arbitrary control flow, and allows it to parse and return partial results while data is still coming in.

3 Likes

This post, “The Best Refactoring You’ve Never Heard Of”, explains in great details how CPS can be used as a first step toward sophisticated algorithm transformations.

In this post, James shows how a transformation, named defunctionalize the continuation, i.e. replacing functions by regular data structures, can be applied to convert recursion to iteration or to implement web actions in a direct style.

3 Likes

Funny enough, trying to use the said syntax to map, I get the following:

#   (* CPS *)
  let map2 f l = 
    let rec mapk f tl k = match tl with
      | [] -> k []
      | hd :: tl -> 
        mapk f tl (fun tl' -> k (f hd :: tl'))
    in 
    mapk f l @@ fun x -> x
;;
val map2 : ('a -> 'b) -> 'a list -> 'b list = <fun>
# module Cont_syntax = struct
  let ( let$ ) x f = fun k -> x (fun y -> f y k)
  let return x = fun k -> k x
end;;
module Cont_syntax :
  sig
    val ( let$ ) : (('a -> 'b) -> 'c) -> ('a -> 'd -> 'b) -> 'd -> 'c
    val return : 'a -> ('a -> 'b) -> 'b
  end
#   let map4 f l =
    let open Cont_syntax in
    let rec mapk f l = match l with
      | [] -> return []
      | hd::tl -> 
        let$ tl' = mapk f tl in
        return @@ f hd :: tl'
    in 
    mapk f l @@ fun x -> x;;
val map4 : ('a -> 'b) -> 'a list -> 'b list = <fun>
# let ex = List.init 1_000_000 (fun i -> i + 1);;
val ex : int list =
  [1; 2; 3; 4; 5; 6; 7; 8; 9; 10; 11; 12; 13; 14; 15; 16; 17; 18; 19; 20; 21; ...]
# map2 (fun x -> x * x) ex;; (* OK *)
- : int list =
[1; 4; 9; 16; 25; 36; 49; 64; 81; 100; 121; 144; 169; 196; 225; 256; 289; 324;; ...]
# map4 (fun x -> x * x) ex;; (* Hmm?! *)
Stack overflow during evaluation (looping recursion?).

Any idea why? Working out the beta-reductions by hand, both versions seem to be equivalent…

Oops, you highlighted a mistake: the syntax is cute but the result is no more tail recursive, loosing the main benefits of a CPS style.

Indeed, if you add [@tailcall] annotations, the compiler issue a Warning 51: expected tailcall:

let map4 f =
    let open Cont_syntax in
    let rec mapk l = match l with
      | [] -> return []
      | hd::tl ->
        let$ tl' = (mapk [@tailcall]) tl in
        return @@ f hd :: tl'
    in
    fun l -> mapk l @@ fun x -> x

The main issue is that the calls to return and let$ are not inlined, even if we add an always [@@inline] annotation.

module Cont_syntax = struct
  let ( let$ ) x f k = x (fun y -> f y k) [@@inline]
  let return x k = k x [@@inline]
end

let map4 f =
    let open Cont_syntax in
    let rec mapk l = match l with
      | [] -> (return [@inlined]) []
      | hd::tl ->
        let$ tl' = (mapk [@tailcall]) tl in
        return @@ f hd :: tl'
    in
    fun l -> mapk l @@ fun x -> x

The compiler issues a clear Warning 55: Cannot inline: Partial application.

In conclusion, the cute syntax does not help :-(.

2 Likes

Efficient compilation of code in continuation-passing style relies on two properties:

  1. Continuations do not escape, so we know that we do not need to allocate a closure to pass a continuation,
  2. Continuations return the type ⊥ (falsity), so we know that applying a continuation can be implemented as a jump.

(Source: Cong et al., Compiling with continuations, or without? whatever.)

For 1) you are relying on inlining to avoid allocating closures. However if you wanted you could still let continuations escape. Abstracted with a monadic interface, this use of CPS is inefficient but allows you to express classical control operators.

For 2) you are relying on tail calls, however if you wanted you could still modify the return value of the continuation. Abstracted with a monadic interface, this use of CPS is inefficient but would let you express delimited continuations.

For 1), a more reliable and compositional constraint is given by types of second-class (i.e. non-escaping) values, or more generally types with region, to ensure that continuations do not need to be allocated on the heap. Many higher-order functions in OCaml, including monadic binds, could benefit if OCaml understood this notion. As a naive approach, this could take the form of a generalisation of the @local attribute to arguments of functions.

For 2), a more reliable and compositional constraint is given by a primitive no-return type (or equivalently a primitive type of negation for the continuation). This could take the form of OCaml knowing to compile applications that return the empty type (type empty = |) as a jump.

Which reminds us of the equation:

programming = structure + efficiency

which I always find of great help when trying to assess papers in programming languages, especially those claiming to find programming truth in abstract mathematical structures.

5 Likes