Wednesday, May 19, 2010

Reading Camlp4, part 6: parsing

In this post I want to discuss Camlp4’s stream parsers and grammars. Since the OCaml parsers in Camlp4 (which we touched on previously) use them, it’s necessary to understand them in order to write syntax extensions; independently, they are a nice alternative to ocamlyacc and other parser generators. Stream parsers and grammars are outlined for the old Camlp4 in the tutorial and manual, but some of the details have changed, and there are many aspects of grammars which are given only a glancing treatment in that material.

Streams and stream parsers

Parsers generated from Camlp4 grammars are built on stream parsers, so let’s start there. It will be easier to explain grammars with this background in hand, and we will see that it is sometimes useful to drop down to stream parsers when writing grammars.

A stream of type 'a Stream.t is a sequence of elements of type 'a. Elements of a stream are accessed sequentially; reading the first element of a stream has the side effect of advancing the stream to the next element. You can also peek ahead into a stream without advancing it. Camlp4 provides a syntax extension for working with streams, which expands to operations on the Stream module of the standard library.

There are various ways to make a stream but we’ll focus on consuming them; for testing you can make a literal stream with the syntax [< '"foo"; '"bar"; '"baz" >]—note the extra single-quotes. With the parser keyword we can write a function to consume a stream by pattern-matching over prefixes of the stream:

let rec p = parser 
  | [< '"foo"; 'x; '"bar" >] -> "foo-bar+" ^ x 
  | [< '"baz"; y = p >] -> "baz+" ^ y 

The syntax '"foo" means match a value "foo"; 'x means match any value, binding it to x, which can be used on the right-hand side of the match as usual; and y = p means call the parser p on the rest of the stream, binding the result to y. You probably get the rough idea, but let’s run it through Camlp4 to see exactly what’s happening:

let rec p (__strm : _ Stream.t) = 
  match Stream.peek __strm with 
  | Some "foo" -> 
      (Stream.junk __strm; 
       (match Stream.peek __strm with 
        | Some x -> 
            (Stream.junk __strm; 
             (match Stream.peek __strm with 
              | Some "bar" -> (Stream.junk __strm; "foo-bar+" ^ x) 
              | _ -> raise (Stream.Error ""))) 
        | _ -> raise (Stream.Error ""))) 
  | Some "baz" -> 
      (Stream.junk __strm; 
       let y = 
         (try p __strm 
          with | Stream.Failure -> raise (Stream.Error "")) 
       in "baz+" ^ y) 
  | _ -> raise Stream.Failure 

We can see that “parser” is perhaps a strong word for this construct; it’s really just a nested pattern match. The generated function peeks the next element in the stream, then junks it once it finds a match (advancing the stream to the next element). If there’s no match on the first token, that’s a Stream.Failure (the stream is not advanced, giving us the opportunity to try another parser); but once we have matched the first token, a subsequent match failure is a Stream.Error (we have committed to a branch, and advanced the stream; if the parse fails now we can’t try another parser).

A call to another parser as the first element of the pattern is treated specially: for this input

let rec p = parser 
  | [< x = q >] -> x 
  | [< '"bar" >] -> "bar" 

we get

let rec p (__strm : _ Stream.t) = 
  try q __strm 
  with 
  | Stream.Failure -> 
      (match Stream.peek __strm with 
       | Some "bar" -> (Stream.junk __strm; "bar") 
       | _ -> raise Stream.Failure) 

So there is a limited means of backtracking: if q fails with Stream.Failure (meaning that the stream has not been advanced) we try the next arm of the parser.

It’s easy to see what would happen if we were to use the same literal as the first element of more than one arm: the first one gets the match. Same if we were to make a recursive call (to the same parser) as the first element: we’d get an infinite loop, since it’s just a function call. So we can’t give arbitrary BNF-like grammars to parser. We could use it as a convenient way to hand-write a recursive-descent parser, but we won’t pursue that idea here. Instead, let’s turn to Camlp4’s grammars, which specify a recursive-descent parser using a BNF-like syntax.

Grammars

Here is a complete example of a grammar:

open Camlp4.PreCast 
module Gram = MakeGram(Lexer) 
let expr = Gram.Entry.mk "expr" 
EXTEND Gram 
  expr: 
    [[ 
       "foo"; x = LIDENT; "bar" -> "foo-bar+" ^ x 
     | "baz"; y = expr -> "baz+" ^ y 
     ]]; 
END 
;; 
try 
  print_endline 
    (Gram.parse_string expr Loc.ghost Sys.argv.(1)) 
with Loc.Exc_located (_, x) -> raise x 

You can build it with the following command:

ocamlfind ocamlc \ 
   -linkpkg -syntax camlp4o \ 
  -package camlp4.extend -package camlp4.lib \ 
  grammar1.ml -o grammar1

Let’s cover the infrastructure before investigating EXTEND. We have a grammar module Gram which we got from Camlp4.PreCast; this is an empty grammar using a default lexer. We have an entry (a grammar nonterminal) expr, which is an OCaml value. We can parse a string starting at an entry using Gram.parse_string (we have to pass it an initial location). We trap Loc.Exc_located (which attaches a location to exceptions raised in parsing) and re-raise the underlying exception so it gets printed. (In subsequent examples I will give just the EXTEND block.)

One way to approach EXTEND is to run the file through Camlp4 (camlp4of has the required syntax extension) to see what we get. This is fun, but the result does not yield much insight; it’s just a simple transformation of the input, passed to Gram.extend. This is the entry point to a pretty hairy bunch of code that generates a recursive descent parser from the value representing the grammar. Let’s take a different tack: RTFM, then run some experiments to shine light in places where the fine manual is a bit dim.

First, what language is parsed by the grammar above? It looks pretty similar to the stream parser example. But what is LIDENT? The stream parser example works with a stream of strings. Here we are working with a stream of tokens, produced by the Lexer module; there is a variant defining the token types in PreCast.mli. The default lexer is OCaml-specific (but it’s often good enough for other purposes); a LIDENT is an OCaml lowercase identifier. A literal string (like "foo") indicates a KEYWORD token; using it in a grammar registers the keyword with the lexer. So the grammar can parse strings like foo quux bar or baz foo quux bar, but not foo bar bar, since bar is a KEYWORD not a LIDENT.

Most tokens have associated strings; x = LIDENT puts the associated string in x. Keywords are given in double quotes (x = KEYWORD works, but I can’t think of a good use for it). You can also use pattern-matching syntax (e.g. `LIDENT x) to get at the actual token constructor, which may carry more than just a string.

You can try the example and see that the lexer takes care of whitespace and OCaml comments. You’ll also notice that the parser ignores extra tokens after a successful parse; to avoid it we need an EOI token to indicate the end of the input (but I haven’t bothered here).

Left-factoring

What happens if two rules start with the same token?

EXTEND Gram 
  expr: 
    [[ 
       "foo"; "bar" -> "foo+bar" 
     | "foo"; "baz" -> "foo+baz" 
     ]]; 
END 

If this were a stream parser, the first arm would always match when the next token is foo; if the subsequent token is baz then the parse fails. But with a grammar, the rules (arms, for a grammar) are left-factored: when there is a common prefix of symbols (a symbol is a keyword, token, or entry—and we will see some others later) among different rules, the parser doesn’t choose which rule to use until the common prefix has been parsed. You can think of a factored grammar as a tree, where the nodes are symbols and the leaves are actions (the right-hand side of a rule is the rule’s action); when a symbol distinguishes two rules, that’s a branching point. (In fact, this is how grammars are implemented: first the corresponding tree is generated, then the parser is generated from the tree.)

What if one rule is a prefix of another?

EXTEND Gram 
  expr: 
    [[ 
       "foo"; "bar" -> "foo+bar" 
     | "foo"; "bar"; "baz" -> "foo+bar+baz" 
     ]]; 
END 

In this case the parser is greedy: if the next token is baz, it uses the second rule, otherwise the first. To put it another way, a token or keyword is preferred over epsilon, the empty string (and this holds for other ways that a grammar can match epsilon—see below about special symbols).

What if two rules call the same entry?

EXTEND Gram 
  GLOBAL: expr; 
 
  f: [[ "quux" ]]; 
 
  expr: 
    [[ 
       "foo"; f; "bar" -> "foo+bar" 
     | "foo"; f; "baz" -> "foo+baz" 
     ]]; 
END 

First, what is this GLOBAL? By default, all entries are global, meaning that they must be pre-defined with Gram.Entry.mk. The GLOBAL declaration gives a list of entries which are global, and makes the rest local, so we don’t need to pre-define them, but we can’t refer to them outside the grammar. Second, note that we can call entries without binding the result to a variable, and that rules don’t need an action—in that case they return (). You can try it and see that factoring works on entries too. Maybe this is slightly surprising, if you’re thinking about the rules as parse-time alternatives, but factoring happens when the parser is built.

What about an entry vs. a token?

EXTEND Gram 
  GLOBAL: expr; 
 
  f: [[ "baz" ]]; 
 
  expr: 
    [[ 
       "foo"; "bar"; f -> "foo+bar" 
     | "foo"; "bar"; "baz" -> "foo+bar+baz" 
     ]]; 
END 

Both rules parse the same language, but an explicit token or keyword trumps an entry or other symbol, so the second rule is used. You can try it and see that the order of the rules doesn’t matter.

What about two different entries?

EXTEND Gram 
  GLOBAL: expr; 
 
  f1: [[ "quux" ]]; 
  f2: [[ "quux" ]]; 
 
  expr: 
    [[ 
       "foo"; f1; "bar" -> "foo+bar" 
     | "foo"; f2; "baz" -> "foo+baz" 
     ]]; 
END 

Factoring happens only within a rule, so the parser doesn’t know that f1 and f2 parse the same language. It commits to the first rule after parsing foo; if after parsing quux it then sees baz, it doesn’t backtrack and try the second rule, so the parse fails. If you switch the order of the rules, then baz succeeds but bar fails.

Local backtracking

Why have two identical entries in the previous example? If we make them different, something a little surprising happens:

EXTEND Gram 
  GLOBAL: expr; 
 
  f1: [[ "quux" ]]; 
  f2: [[ "xyzzy" ]]; 
 
  expr: 
    [[ 
       "foo"; f1; "bar" -> "foo+bar" 
     | "foo"; f2; "baz" -> "foo+baz" 
     ]]; 
END 

Now we can parse both foo quux bar and foo xyzzy baz. How does this work? It takes a little digging into the implementation (which I will spare you) to see what’s happening: the "foo" keyword is factored into a common prefix, then we have a choice between f1 and f2. A choice betwen entries generates a stream parser, with an arm for each entry which calls the entry’s parser. As we saw in the stream parsers sections, calling another parser in the first position of a match compiles to a limited form of backtracking. So in the example, if f1 fails with Stream.Failure (which it does when the next token is not quux) then the parser tries to parse f2 instead.

Local backtracking works only when the parser is at a branch point (e.g. a choice between two entries), and when the called entry does not itself commit and advance the stream (in which case Stream.Error is raised on a parse error instead of Stream.Failure). Here is an example that fails the first criterion:

EXTEND Gram 
  GLOBAL: expr; 
 
  f1: [[ "quux" ]]; 
  f2: [[ "xyzzy" ]]; 
  g1: [[ "plugh" ]]; 
  g2: [[ "plugh" ]]; 
 
  expr: 
    [[ 
       g1; f1 -> "f1" 
     | g2; f2 -> "f2" 
     ]]; 
END 

After parsing g1, the parser has committed to the first rule, so it’s not possible to backtrack and try the second if f1 fails.

Here’s an example that fails the second criterion:

EXTEND Gram 
  GLOBAL: expr; 
 
  g: [[ "plugh" ]]; 
  f1: [[ g; "quux" ]]; 
  f2: [[ g; "xyzzy" ]]; 
 
  expr: 
    [[ f1 -> "f1" | f2 -> "f2" ]]; 
END 

When f1 is called, after parsing g the parser is committed to f1, so if the next token is not quux the parse fails rather than backtracking.

Local backtracking can be used to control parsing with explicit lookahead. We could repair the previous example as follows:

let test = 
  Gram.Entry.of_parser "test" 
    (fun strm -> 
       match Stream.npeek 2 strm with 
         | [ _; KEYWORD "xyzzy", _ ] -> raise Stream.Failure 
         | _ -> ()) 
EXTEND Gram 
  GLOBAL: expr; 
 
  g: [[ "plugh" ]]; 
  f1: [[ g; "quux" ]]; 
  f2: [[ g; "xyzzy" ]]; 
 
  expr: 
    [[ test; f1 -> "f1" | f2 -> "f2" ]]; 
END 

We create an entry from a stream parser with Gram.Entry.of_parser. This could do some useful parsing and return a value just like any other entry, but here we just want to cause a backtrack (by raising Stream.Failure) if the token after the next one is xyzzy. We can see it with Stream.npeek 2, which returns the next two tokens, but does not advance the stream. (The stream parser syntax is not useful here since it advances the stream on a match.) You can see several examples of this technique in Camlp4OCamlParser.ml.

We have seen that for stream parsers, a match of a sequence of literals compiles to a nested pattern match; as soon as the first literal matches, we’re committed to that arm. With grammars, however, a sequence of tokens (or keywords) is matched all at once: enough tokens are peeked; if all match then the stream is advanced past all of them; if any fail to match, Stream.Failure is raised. So in the first example of this section, f1 could be any sequence of tokens, and local backtracking would still work. Or it could be a sequence of tokens followed by some non-tokens; as long as the failure happens in the sequence of tokens, local backtracking would still work.

Self-calls

Consider the following grammar:

EXTEND Gram 
  GLOBAL: expr; 
 
  b: [[ "b" ]]; 
 
  expr: 
    [[ expr; "a" -> "a" | b -> "b" ]]; 
END 

We’ve seen that a choice of entries generates a stream parser with an arm for each entry, and also that a call to another parser in a stream parser match is just a function call. So it seems like the parser should go into a loop before parsing anything.

However, Camlp4 gives calls to the entry being defined (“self-calls”) special treatment. The rules of an entry actually generate two parsers, the “start” and “continue” parsers (these names are taken from the code). When a self-call appears as the first symbol of a rule, the rest of the rule goes into the continue parser; otherwise the whole rule goes into the start parser. An entry is parsed starting with the start parser; a successful parse is followed by the continue parser. So in the example, we first parse using just the second rule, to get things off the ground, then parse using just the first rule. If there are no start rules (that is, all rules begin with self-calls) the parser doesn’t loop, but it fails without parsing anything.

Levels and precedence

I am sorry to say that I have not been completely honest with you. I have made it seem like entries consist of a list of rules in double square brackets. In fact, entries are lists of levels, in single square brackets, and each level consists of a list of rules, also in single square brackets. So each of the examples so far has contained only a single level. Here is an example with multiple levels:

EXTEND Gram 
  expr: 
    [ [ x = expr; "+"; y = expr -> x + y 
      | x = expr; "-"; y = expr -> x - y ] 
    | [ x = expr; "*"; y = expr -> x * y 
      | x = expr; "/"; y = expr -> x / y ] 
    | [ x = INT -> int_of_string x 
      | "("; e = expr; ")" -> e ] ]; 
END 

(You’ll need a string_of_int to use this grammar with the earlier framework.) The idea with levels is that parsing begins at the topmost level; if no rule applies in the current level, then the next level down is tried. Furthermore, when making a self-call, call at the current level (or the following level; see below) rather than at the top. This gives a way to implement operator precedence: order the operators top to bottom from loosest- to tightest-binding.

Why does this work? The multi-level grammar is just a “stratified” grammar, with a little extra support from Camlp4; we could write it manually like this:

EXTEND Gram 
  GLOBAL: expr; 
 
  add_expr: 
    [[ 
       x = add_expr; "+"; y = mul_expr -> x + y 
     | x = add_expr; "-"; y = mul_expr -> x - y 
     | x = mul_expr -> x 
     ]]; 
 
  mul_expr: 
    [[ 
       x = mul_expr; "*"; y = base_expr -> x * y 
     | x = mul_expr; "/"; y = base_expr -> x / y 
     | x = base_expr -> x 
     ]]; 
 
  base_expr: 
    [[ 
       x = INT -> int_of_string x 
     | "("; e = add_expr; ")" -> e 
     ]]; 
 
  expr: [[ add_expr ]]; 
END 

When parsing a mul_expr, for instance, we don’t want to parse an add_expr as a subexpression; 1 * 2 + 3 should not parse as 1 * (2 + 3). A stratified grammar just leaves out the rules for lower-precedence operators at each level. Why do we call add_expr on the left side of + but mul_expr on the right? This makes + left-associative; we parse 1 + 2 + 3 as (1 + 2) + 3 since add_expr is a possibility only on the left. (For an ordinary recursive-descent parser we’d want right-associativity to prevent looping, although the special treatment of self-calls makes the left-associative version work here.)

Associativity works just the same with the multi-level grammar. By default, levels are left-associative: in the start parser (for a self-call as the first symbol of the rule), the self-call is made at the same level; in the continue parser, self-calls are made at the following level. For right-associativity it’s the reverse, and for non-associativity both start and continue parsers call the following level. The associativity of a level can be specified by prefixing it with the keywords NONA, LEFTA, or RIGHTA. (Either I don’t understand what non-associativity means, or NONA is broken; it seems to be the same as LEFTA.)

Levels may be labelled, and the level to call may be given explicitly. So another way to write the same grammar is:

EXTEND Gram 
  expr: 
    [ "add" 
      [ x = expr LEVEL "mul"; "+"; y = expr LEVEL "add" -> x + y 
      | x = expr LEVEL "mul"; "-"; y = expr LEVEL "add" -> x - y 
      | x = expr LEVEL "mul" -> x ] 
    | "mul" 
      [ x = expr LEVEL "base"; "*"; y = expr LEVEL "mul" -> x * y 
      | x = expr LEVEL "base"; "/"; y = expr LEVEL "mul" -> x / y 
      | x = expr LEVEL "base" -> x ] 
    | "base" 
      [ x = INT -> int_of_string x 
      | "["; e = expr; "]" -> e ] ]; 
END 

(Unfortunately, the left-associative version of this loops; explicitly specifying a level when calling an entry defeats the start / continue mechanism, since the call is not recognized as a self-call.) Calls to explicit levels can be used when calling other entries, too, not just for self calls. Level names are also useful for extending grammars, although we won’t cover that here.

Special symbols

There are several special symbols: SELF refers to the entry being defined (at the current or following level depending on the associativity and the position of the symbol in the rule, as above); NEXT refers to the entry being defined, at the following level regardless of associativity or position.

A list of zero or more items can be parsed with the syntax LIST0 elem, where elem can be any other symbol. The return value has type 'a list when elem has type 'a. To parse separators between the elements use LIST0 elem SEP sep; again sep can be any other symbol. LIST1 means parse one or more items. An optional item can be parsed with OPT elem; the return value has type 'a option. (Both LIST0 and OPT can match the empty string; see the note above about the treatment of epsilon.)

Finally, a nested set of rules may appear in a rule, and acts like an anonymous entry (but can have only one level). For example, the rule

  x = expr; ["+" | "plus"]; y = expr -> x + y 

parses both 1 + 2 and 1 plus 2.

Addendum: A new special symbol appeared in the 3.12.0 release, TRY elem, which provides non-local backtracking: a Stream.Error occurring in elem is converted to a Stream.Failure. (It works by running elem on an on-demand copy of the token stream; tokens are not consumed from the real token stream until elem succeeds.) TRY replaces most (all?) cases where you’d need to drop down to a stream parser for lookahead. So another way to fix the local backtracking example above is:

EXTEND Gram 
  GLOBAL: expr; 
 
  g: [[ "plugh" ]]; 
  f1: [[ g; "quux" ]]; 
  f2: [[ g; "xyzzy" ]]; 
 
  expr: 
    [[ TRY f1 -> "f1" | f2 -> "f2" ]]; 
END 

Almost the whole point of Camlp4 grammars is that they are extensible—you can add rules and levels to entries after the fact—so you can modify the OCaml parsers to make syntax extensions. But I am going to save that for a later post.

Friday, May 7, 2010

How froc works

I am happy to announce the release of version 0.2 of the froc library for functional reactive programming in OCaml. There are a number of improvements:

  • better event model: there is now a notion of simultaneous events, and behaviors and events can now be freely mixed
  • self-adjusting computation is now supported via memo functions; needless recomputation can be avoided in some cases
  • faster priority queue and timeline data structures
  • behavior and event types split into co- and contra-variant views for subtyping
  • bug fixes and cleanup

Development of froc has moved from Google Code to Github; see

Thanks to Ruy Ley-Wild for helpful discussion, and to Daniel Bünzli for helpful discussion and many good ideas in React.

I thought I would take this opportunity to explain how froc works, because it is interesting, and to help putative froc users use it effectively.

Dependency graphs

The main idea behind froc (and self-adjusting computation) is that we can think of an expression as implying a dependency graph, where each subexpression depends on its subexpressions, and ultimately on some input values. When the input values change, we can recompute the expression incrementally by recursively pushing changes to dependent subexpressions.

To be concrete, suppose we have this expression:

  let u = v / w + x * y + z 

Here is a dependency graph relating expressions to their subexpressions:

The edges aren’t directed, because we can think of dependencies as either demand-driven (to compute A, we need B), or change-driven (when B changes, we must recompute A).

Now suppose we do an initial evaluation of the expression with v = 4, w = 2, x = 2, y = 3, and z = 1. Then we have (giving labels to unlabelled nodes, and coloring the current value of each node green):

If we set z = 2, we need only update u to 10, since no other node depends on z. If we then set v = 6, we need to update n0 to 3, n2 to 9 (since n2 depends on n0), and u to 11, but we don’t need to update n1. (This is the change-driven point of view.)

What if we set z = 2 and v = 6 simultaneously, then do the updates? We have to be careful to do them in the right order. If we updated u first (since it depends on z), we’d use a stale value for n2. We could require that we don’t update an expression until each of its dependencies has been updated (if necessary). Or we could respect the original evaluation order of the expressions, and say that we won’t update an expression until each expression that came before it has been updated.

In froc we take the second approach. Each expression is given a timestamp (not a wall-clock time, but an abstract ordered value) when it’s initially evaluated, and we re-evaluate the computation by running through a priority queue of stale expressions, ordered by timestamp. Here is the situation, with changed values in magenta, stale values in red, and timestamps in gray:

If we update the stale nodes from their dependencies in timestamp order, we get the right answer. We will see how this approach gives us a way to handle control dependencies, where A does not depend on B, but A’s execution is controlled by B.

Library interface

The core of froc has the following (simplified) signature:

  type 'a t 
  val return : 'a -> 'a t 
  val bind : 'a t -> ('a -> 'b t) -> 'b t 

The type 'a t represents changeable values (or just changeables) of type 'a; these are the nodes of the dependency graph. Return converts a regular value to a changeable value. Bind makes a new changeable as a dependent of an existing one; the function argument is the expression that computes the value from its dependency. We have >>= as an infix synonym for bind; there are also multi-argument versions (bind2, bind3, etc.) so a value can depend on more than one other value.

We could translate the expression from the previous section as:

  let n0 = bind2 v w (fun v w -> return (v / w)) 
  let n1 = bind2 x y (fun x y -> return (x * y)) 
  let n2 = bind2 n0 n1 (fun n0 n1 -> return (n0 + n1)) 
  let u = bind2 n2 z (fun n2 z -> return (n2 + z)) 

There are some convenience functions in froc to make this more readable (these versions are also more efficient):

  val blift : 'a t -> ('a -> 'b) -> 'b t 
  val lift : ('a -> 'b) -> 'a t -> 'b t 

Blift is like bind except that you don’t need the return at the end of the expression (below we’ll see cases where you actually need bind); lift is the same as blift but with the arguments swapped for partial application. So we could say

  let n0 = blift2 v w (fun v w -> v / w) 
  let n1 = blift2 x y (fun x y -> x * y) 
  let n2 = blift2 n0 n1 (fun n0 n1 -> n0 + n1) 
  let u = blift2 n2 z (fun n2 z -> n2 + z) 

or even

  let (/) = lift2 (/) 
  let ( * ) = lift2 ( * ) 
  let (+) = lift2 (+) 
  let u = v / w + x * y + z 

Now, there is no reason to break down expressions all the way—a node can have a more complicated expression, for example:

  let n0 = blift2 v w (fun v w -> v / w) 
  let n2 = blift3 n0 x y (fun n0 x y -> n0 + x * y) 
  let u = blift2 n2 z (fun n2 z -> n2 + z) 

There is time overhead in propagating dependencies, and space overhead in storing the dependency graph, so it’s useful to be able to control the granularity of recomputation by trading off computation over changeable values with computation over ordinary values.

Dynamic dependency graphs

Take this expression:

  let b = x = 0 
  let y = if b then 0 else 100 / x 

Here it is in froc form:

  let b = x >>= fun x -> return (x = 0) 
  let n0 = x >>= fun x -> return (100 / x) 
  let y = bind2 b n0 (fun b n0 -> if b then return 0 else n0) 

and its dependency graph, with timestamps:

(We begin to see why bind is sometimes necessary instead of blift—in order to return n0 in the else branch, the function must return 'b t rather than 'b.)

Suppose we have an initial evaluation with x = 10, and we then set x = 0. If we blindly update n0, we get a Division_by_zero exception, although we get no such exception from the original code. Somehow we need to take into account the control dependency between b and 100 / x, and compute 100 / x only when b is false. This can be accomplished by putting it inside the else branch:

  let b = x >>= fun x -> return (x = 0) 
  let y = b >>= fun b -> if b then return 0 
                              else x >>= fun x -> return (100 / x) 

How does this work? Froc keeps track of the start and finish timestamps when running an expression, and associates dependencies with the timestamp when they are attacheed. When an expression is re-run, we detach all the dependencies between the start and finish timestamps. In this case, when b changes, we detach the dependent expression that divides by 0 before trying to run it.

Let’s walk through the initial run with x = 10: Here is the graph showing the timestamp ranges, and on the dependency edges, the timestamp when the dependency was attached:

First we evaluate b (attaching it as a dependent of x at time 0) to get false. Then we evaluate y (attaching it as a dependent of b at time 3): we check b and evaluate n0 to get 10 (attaching it as a dependent of x at time 5). Notice that we have a dependency edge from y to n0. This is not a true dependency, since we don’t recompute y when n0 changes; rather the value of y is a proxy for n0, so when n0 changes we just forward the new value to y.

What happens if we set x = 20? Both b and n0 are stale since they depend on x. We re-run expressions in order of their start timestamp, so we run b and get false. Since the value of b has not changed, y is not stale. Then we re-run n0, so its value (and the value of y by proxy) becomes 5.

What happens if we set x = 0? We run b and get true. Now y is also stale, and it is next in timestamp order. We first detach all the dependencies in the timestamp range 4-9 from the previous run of y: the dependency of n0 on x and the proxy dependency of y on n0. This time we take the then branch, so we get 0 without attaching any new dependencies. We are done; no Division_by_zero exception.

Now we can see why it’s important to handle updates in timestamp order: the value which decides a control flow point (e.g. the test of an if) is always evaluated before the control branches (the then and else branches), so we have the chance to fix up the dependency graph before the branches are updated.

Garbage collection and cleanup functions

A node points to its dependencies (so it can read their values when computing its value), and its dependencies point back to the node (so they can mark it stale when they change). This creates a problem for garbage collection: a node which becomes garbage (from the point of view of the library user) is still attached to its dependencies, taking up memory, and causing extra recomputation.

The implementation of dynamic dependency graphs helps with this problem: as we have seen, when an expression is re-run, the dependencies attached in the course of the previous run are detached, including any dependencies for nodes which have become garbage. Still, until the expression that created them is re-run, garbage nodes remain attached.

Some other FRP implementations use weak pointers to store a node’s dependents, to avoid hanging on to garbage nodes. Since froc is designed to work in browsers (using ocamljs), weak pointers aren’t an option because they aren’t supported in Javascript. But even in regular OCaml, there are reasons to eschew the use of weak pointers:

First, it’s useful to be able to set up changeable expressions which are used for their effect (say, updating the GUI) rather than their value; to do this with a system using weak pointers, you have to stash the expression somewhere so it won’t be GC’d. This is similar to the problem of GCing threads; it doesn’t make sense if the threads can have an effect.

Second, there are other resources which may need to be cleaned up in reaction to changes (say, GUI event handler registrations); weak pointers are no help here. Froc gives you a way to set cleanup functions during a computation, which are run when the computation is re-run, so you can clean up other resources.

With froc there are two options to be sure you don’t leak memory: you can call init to clean up the entire system, or you can use bind to control the lifetime of changeables: for instance, you could have a changeable c representing a counter, do a computation in the scope of a bind of c (you can just ignore the value), then increment the counter to clear out the previous computation.

In fact, there are situations where froc cleans up too quickly—when you want to hang on to a changeable after the expression that attached it is re-run. We’ll see shortly how to avoid this.

Memoizing the previous run

Here is the List.map function, translated to work over lists where the tail is changeable.

  type 'a lst = Nil | Cons of 'a * 'a lst t 
 
  let rec map f lst = 
    lst >>= function 
      | Nil -> return Nil 
      | Cons (h, t) -> 
          let t = map f t in 
          return (Cons (f h, t)) 

What happens if we run

  map (fun x -> x + 1) [ 1; 2; 3 ] 

? (I’m abusing the list syntax here to mean a changeable list with these elements.) Let’s see if we can fit the dependency graph on the page (abbreviating Cons and Nil and writing just f for the function expression):

(The dependency edges on the right-hand side don’t mean that e.g. f0 depends directly on f1, but rather that the value returned by f0Cons(2,f1)—depends on f1. We don’t re-run f0 when f1 changes, or even update its value by proxy as we did in the previous section. But if f1 is stale it must be updated before we can consider f0 up-to-date.)

Notice how the timestamp ranges for the function expressions are nested each within the previous one. There is a control dependency at each recursive call: whether we make a deeper call depends on whether the argument list is Nil.

So if we change t3, just f3 is stale. But if we change t0, we must re-run f0, f1, f2, and f3—that is, the whole computation—detaching all the dependencies, then reattaching them. This is kind of annoying; we do a lot of pointless work since nothing after the first element has changed.

If only some prefix of the list has changed, we’d like to be able to reuse the work we did in the previous run for the unchanged suffix. Froc addresses this need with memo functions. In a way similar to ordinary memoization, a memo function records a table of arguments and values when you call it. But in froc we only reuse values from the previous run, and only those from the timestamp range we’re re-running. We can define map as a memo function:

  let map f lst = 
    let memo = memo () in 
    let rec map lst = 
      lst >>= function 
        | Nil -> return Nil 
        | Cons (h, t) -> 
            let t = memo map t in 
            return (Cons (f h, t)) in 
    memo map lst 

Here the memo call makes a new memo table. In the initial run we add a memo entry associating each list node (t0, t1, …) with its map (f0, f1, …). Now, suppose we change t0: f0 is stale, so we update it. When we go to compute map f t1 we get a memo hit returning f1 (the computation of f1 is contained in the timestamp range of f0, so it is a candidate for memo matching). F1 is up-to-date so we return it as the value of map f t1.

There is a further wrinkle: suppose we change both t0 and t2, leaving t1 unchanged. As before, we get a memo hit on t1 returning f1, but since f2 is stale, so is f1. We must run the update queue until f1 is up-to-date before we return it as the value of map f t1. Recall that we detach the dependencies of the computation we’re re-running; in order to update f1 we just leave it attached to its dependencies and run the queue until the end of its timestamp range.

In general, there can be a complicated pattern of changed and unchanged data—we could change every other element in the list, for instance—so memoization and the update loop call one another recursively. From the timestamp point of view, however, we can think of it as a linear scan through time, alternating between updating stale computations and reusing ones which have not changed.

The memo function mechanism provides a way to keep changeables attached even after the expression that attached them is re-run. We just need to attach them from within a memo function, then look them up again on the next run, so they’re left attached to their dependencies. The quickhull example (source) demonstrates how this works.

Functional reactive programming and the event queue

Functional reactive programming works with two related types: behaviors are values that can change over time, but are defined at all times; events are defined only at particular instants in time, possibly (but not necessarily) with a different value at each instant. (Signals are events or behaviors when we don’t care which one.)

Events can be used to represent external events entering the system (like GUI clicks or keystrokes), and can also represent occurrences within the system, such as a collision between two moving objects. It is natural for events to be defined in terms of behaviors and vice versa. (In fact they can be directly interdefined with the hold and changes functions.)

In froc, behaviors are just another name for changeables. Events are implemented on top of changeables: they are just changeables with transient values. An incoming event sets the value of its underlying changeable; after changes have propagated through the dependency graph, the values of all the changeables which underlie events are removed (so they can be garbage collected).

Signals may be defined (mutually) recursively. For example, in the bounce example (source), the position of the ball is a behavior defined in terms of its velocity, which is a behavior defined in terms of events indicating collisions with the walls and paddle, which are defined in terms of the ball’s position.

Froc provides the fix_b and fix_e functions to define signals recursively. The definition of a signal can’t refer directly to its own current value, since it hasn’t been determined yet; instead it sees its value from the previous update cycle. When a recursively-defined signal produces a value, an event is queued to be processed in the next update cycle, so the signal can be updated based on its new current value. (If the signal doesn’t converge somehow this process loops.)

Related systems

Froc is closely related to a few other FRP systems which are change-driven and written in an imperative, call-by-value language:

FrTime is an FRP system for PLT Scheme. FrTime has a dependency graph and update queue mechanism similar to froc, but sorts stale nodes in dependency (“topological”) rather than timestamp order. There is a separate mechanism for handling control dependencies, using a dynamic scoping feature specific to PLT Scheme (“parameters”) to track dependencies attached in the course of evaluating an expression; in addition FrTime uses weak pointers to collect garbage nodes. There is no equivalent of froc’s memo functions. Reactivity in FrTime is implicit: you give an ordinary Scheme program, and the compiler turns each subexpression into a changeable value. There is no programmer control over the granularity of recomputation, but there is a compiler optimization (“lowering”) which recovers some performance by coalescing changeables.

Flapjax is a descendent of FrTime for Javascript. It implements the same dependency-ordered queue as FrTime, but there is no mechanism for control dependencies, and there are no weak pointers (since there are none in Javascript), so it is fairly easy to create memory leaks (although there is a special reference-counting mechanism in certain cases). Flapjax can be used as a library; it also has a compiler similar to FrTime’s, but since it doesn’t handle control dependencies, the semantics of compiled programs are not preserved (e.g. you can observe exceptions that don’t occur in the original program).

React is a library for OCaml, also based on a dependency-ordered queue, using weak pointers, without a mechanism for control dependencies.

Colophon

I used Mlpost to generate the dependency graph diagrams. It is very nice!