Static exceptions.

Alain Frisch

In this post, I propose Static Exceptions as a new language feature allowing programmers to express interesting control flows in a compact way.

As a motivating examples, let’s consider the following task: write a function of type float array array -> int * int returning the indices (i, j) (in lexicographic order) of the first cell in the input matrix such that the sum of all cells until that cell (included) is negative, and (-1, -1) if no such cell exist. And try to make this function fast.

A functional programmer might write something like:

let find_rec m =
  let rec loop_i r i =
    if i = Array.length m then (-1, -1)
    else let a = m.(i) in
    let rec loop_j r j =
      if j = Array.length a then loop_i r (succ i)
      else let r = r +. a.(j) in
      if r < 0. then (i, j)
      else loop_j r (succ j)
    in
    loop_j r 0
  in
  loop_i 0. 0

Tail-recursion and local functions are particularly efficient in OCaml, so this should not be too slow. A programmer more used to standard imperative style (or a very good OCaml programmer who knows that elimination of float boxing only occurs within a single function body) might prefer for-loops, and an exception to exit early when the cell is found:

exception Result of (int * int)

let find_exn m =
  let r = ref 0. in
  try
    for i = 0 to Array.length m - 1 do
      let a = m.(i) in
      for j = 0 to Array.length a - 1 do
        r := !r +. a.(j);
        if !r < 0. then raise (Result (i, j))
      done
    done;
    (-1, -1)
  with Result x -> x

Exceptions are very fast in OCaml, so this should not be too slow. Let’s compare the performance of those two versions, with the following main program:

let () =
  let m = [| [| 10.; 20.; 30. |]; [| -10. |]; [| -20.; -40.; -10.; -10.; |] |] in
  for i = 1 to 100000000 do
    ignore (find_rec (*find_exn*) m)
  done

Here are the results on my machine (using ocamlopt, in seconds):

find_rec3.45
find_exn1.70

And the winner is find_exn! One could even imagine it becomes better with some simple bound-check elimination pass (much easier to do on explicit for-loop between 0 and Array.length - 1 than on loops encoded with tail-recursion).

I have some bad news: as soon as you enable backtraces (compiling with -g and running with OCAMLRUNPARAM=b=1), exceptions are not so fast anymore: find_exn now take 4.10s (slower than the recursive version). In many cases, it is not really an option to disable backtraces “in production”, because we want nice error messages for unexpected exceptions (i.e. real errors, not exceptions used for explicit control flow).

Even without considering performances, the approach based on exceptions has several drawbacks.

  • First, it is a little bit inconvenient having to declare the exception explicitly outside the function, even if it is purely local (and you don’t benefit from type-inference for the exception arguments). Also, you are stuck if you are in a polymorphic function and the exception needs to take an argument involving its universal type variables. Work-arounds exist, but they introduce extra syntactic noise to the algorithm (either passing values using a local reference, or defining a exception in a local module, after taking care of materialising type variables as locally abstract types).

  • Second, exceptions make it more difficult to reason about the code and introduce opportunities for subtle bugs. This might not be seen on the example above, but it is very easy to let an exception escape its intended scope.

Introducing Static Exceptions

I propose to extend OCaml with Static Exceptions to address issues with exceptions used for local control flow. Static Exceptions have the same dynamic semantics than regular exceptions, but they are implicitly declared by a specific try…with block and are only meaningful within its body. Moreover, they come with a restriction that they cannot be raised in a sub-function inside the body. This guarantees that at runtime, they can only be raised during the evaluation of the body, and the consequence is that the compiler can implement such a raise very efficiently, just as a jump to the corresponding handler.

I’ve implemented this proposal in a branch of the OCaml SVN (branches/static_exceptions) and proposed it for inclusion (http://caml.inria.fr/mantis/view.php?id=5879). The syntax needs to be discussed. Currently, I’ve piggy-backed the syntax of polymorphic variants, mostly to avoid messing up with the parser, and also because static exceptions shares with polymorphic variants the fact that they don’t need to be declared explicitly (as opposed to regular exceptions and regular variant types). With this syntax, our running example can be written like that:

let find_static_exn m =
  let r = ref 0. in
  try
    for i = 0 to Array.length m - 1 do
      let a = m.(i) in
      for j = 0 to Array.length a - 1 do
        r := !r +. a.(j);
        if !r < 0. then raise (`Return (i, j))
      done
    done;
    (-1, -1)
  with `Return x -> x

Note that the local exception (`Return) does not need to be declared. I find this kind of code quite nice to read. Moreover, it is the most efficient version I’ve been able to write:

find_rec3.45
find_exn1.70
find_exn (backtraces enabled)4.10
find_static_exn1.38

Of course, one should not infer too much from this benchmark. For instance, if we change the input to the function so that the target is found on the first cell (i.e. replace the first cell with a negative number), we can get quite different results:
find_rec1.33
find_exn0.76
find_exn (backtraces enabled)2.90
find_static_exn0.48

Use cases

Our running example suggests a first class of situations where Static Exceptions are very useful: imperatives loops (for, while), with finer control on exit conditions. Basically, whenever you would use break statements in C to exit a loop (not necessarily the innermost one, in cases of nested loops).

Static Exception can also simulate a return statement, also demonstrated by our running example. Here is an example:

type t = {name:string; address:string; country:string}

let ask s =
  print_endline s;
  let s = read_line () in
  if s = "" then None else Some s

let f () =
  try
    let name = match ask "Name" with Some s -> s | None -> raise `Abort in
    let address = match ask "Address" with Some s -> s | None -> raise `Abort in
    let country = match ask "Country" with Some s -> s | None -> raise `Abort in
    Some {name; address; country}
  with `Abort ->
    None

Other ways to implement such sequences of actions with possible early exits are a little-bit cumbersome, or create very nested code.

An even more interesting use of Static Exception is to share continuations. Consider a complex and nested pattern matching where several branches need to do the same thing (possibly on different values).

let f x a =
  try
    match x with
    | Foo x ->
        begin match categorize x with
        | A | B -> raise (`Cont x)
        | C -> 0
        end
    | Bar (x, y) ->
        begin match categorize x with
        | A -> raise (`Cont y)
        | B | C -> 1
        end
  with `Cont y -> ... a ...

A standard way to write such code would probably not be with exceptions, but with a local function:

let f x a =
  let cont x = ... a ... in
  match x with
  | Foo x ->
      begin match categorize x with
      | A | B -> cont x
      | C -> 0
      end
  | Bar (x, y) ->
      begin match categorize x with
      | A -> cont y
      | B | C -> 1
      end

This is possible, because the raise statements are in tail position (which is not always the case). Anyway, this approach based on local functions is fine, but it induces a non-negligible runtime overhead, because the closures corresponding to the local functions need to be allocated. (Imagine a case where there would be several shared continuations: each of them would require a local function even though one of them would be used on each execution.)

Yet another situation where Static Exceptions might be useful is to escape a (regular) exception handler. This can be useful: (i) to make it clear that we are not longer interested in capturing exceptions during the evaluation of some sub-expression, or (ii) to restore tail calls. Consider:

let rec f = function
  | [] -> ()
  | (x, y) :: tl ->
     try
       let x' = Hashtbl.find tbl x in
       let y' = Hashtbl.find tbl y in
       if foo x' y' then f tl
     with Not_found -> print_endline "..."

Static Exceptions allow to guarantee that the Not_found exception handler will not capture an exception raise by foo, and also to ensure that the function is tail-recursive.

let rec f = function
  | [] -> ()
  | (x, y) :: tl ->
     try
       let x' = Hashtbl.find tbl x in
       let y' = Hashtbl.find tbl y in
       raise (`Cont (x', y'))
     with
     | Not_found -> print_endline "..."
     | `Cont (x', y') -> if foo x' y' then f tl

Achieving the same behavior without (static) exceptions requires building an intermediate value:

let rec f = function
  | [] -> ()
  | (x, y) :: tl ->
     let r =
       try
         let x' = Hashtbl.find tbl x in
         let y' = Hashtbl.find tbl y in
         Some (x', y')
       with Error s -> None
     in
     match r with
     | Some (x', y') -> if foo x' y' then f tl
     | None -> print_endline "..."

Note that the body of a try…with block with only static exceptions is considered to be in tail position (i.e. it does not break tail-calls as regular try…with blocks do).

A new language feature vs optimisation

Static Exceptions have the same behavior as regular exceptions, only with some restrictions on where they can be used (allowing a lighter syntax without declaration, and a vastly optimised implementation). It makes sense to wonder whether it is worth introducing a new notion to the language rather than to rely on regular exceptions and implement some clever optimisations in the compiler to detect exceptions used “statically” and retrieve the great performance profile of Static Exceptions. Of course, this would not allow to omit declarations (which again, is particularly tedious for polymorphic functions), but it would avoid complexifying the language. I believe this is not a good approach, for several reasons.

A minor argument to start: the semantics might not be exactly the same, because of backtraces. It is easier to document the fact that backtraces are not available for Static Exceptions than to explain that some optimisation might break some forms of exception w.r.t. backtraces.

Something more problematic is that given the difference of performance between regular and static exceptions (particularly when backtraces are enabled), it is important that users (who care about performances) know about the notion of static exceptions, whether it is an explicit notion (with a dedicated syntax) or whether it is introduced implicitly by optimisations in the compiler. I find it much easier to describe the concept if the notion is explicit. The same argument could be applied to tail-calls themselves (serious users need to know about this concept, even if it is not materialised as a language feature), but tail-calls are much simpler to describe than those cases where exceptions can be turned automatically into Static Exceptions.

Related to the point above: an optimisation-based version of Static Exceptions would be quite complex and fragile. It is quite difficult to guarantee that an exception cannot be raised outside the evaluation of the body of the try…with. Basically, the only way to guarantee it without requiring complex static analysis is the syntactic criterion applied to Static Exceptions (used only within the syntactic scope of a given try…with body, as an argument of raise, and not under a local abstraction). So an optimisation would probably detect cases where the exception is defined in a local module (

let module M = struct exception E
  of ... end in ....

) in the function, and used only as an argument of raise statements in the body of a try…with block (and not under abstractions). This is quite ad hoc, and the users need to know exactly which form is recognized if they want to benefit from good performances (and in particular avoid breaking performances by doing some local refactoring of the code). I’m clearly in favor of a well-defined notion (with an explicit syntax). That said, it could make sense to transform automatically some patterns of code into static exceptions, as an optimisation pass. But rather than doing it for regular exceptions, I believe it is more interesting in practice to try to optimise local functions introduced to share continuations. This is a very common situation where I don’t believe people typically think about using exceptions (and they are probably right!).

Some words about the implementation

How difficult is it to extend OCaml with Static Exceptions? Well, actually, this is quite easy, because most of the machinery is already in place. The Lambda internal language (the last common intermediate language before the byte code and the native code compiler diverge) has exactly this notion (Lstaticcatch/Lstaticraise), which is used to compile pattern matching. Basically, in the branch, I’ve only had to expose this notion to the user (currently, without changing the syntax, only the type-checking rule for try..with blocks and for raise statements).

A minor point is that an optimisation pass currently assumes that Lstaticraise operations only appear in tail-position within the corresponding Lstaticcatch handler (in order to inline the handler in place of the Lstaticraise when there is a single instance of the Lstaticraise). This is no longer true, but it is trivial to disable the optimisation for Static Exceptions (and it would not be very difficult to re-enable it even for Static Exceptions when it is safe).

A less minor point is that Static Exceptions can cross (regular) exception handlers. Concretely, at runtime, OCaml programs maintain a stack of exception handlers which protect the current (dynamic) scope. The only way to leave an exception handler (i.e. to pop it from this stack) is either to succeed (the last handler is discarded from the stack) or to raise an exception (which is then passed to the last handler). Now, Static Exceptions can jump to a static handler outside the inner-most dynamic exception handler(s). It is necessary to take this into account and remove those handler(s) from the stack. This required to adapt both the byte code compiler (commit 13222) and the native code compiler (commit 13223).

It this new feature is accepted, the current implementation will need to be improved: better error messages, support for deep pattern matching on the arguments of Static Exceptions, and probably a different syntax.

Drawbacks

The most serious drawback I can see with Static Exceptions is that the restriction on where they can be raised forbids some useful code factorisation. For instance, one of the examples above was:

 let name = match ask "Name" with Some s -> s | None -> raise `Abort in
    let address = match ask "Address" with Some s -> s | None -> raise `Abort in
    let country = match ask "Country" with Some s -> s | None -> raise `Abort in
    ...

It is tempting to factorise it to:

let ask_abort s = match ask s with Some s -> s | None -> raise `Abort in
    let name = ask_abort "Name" in
    let address = ask_abort "Address" in
    let country = ask_abort "Country" in
    ...

but it is not possible to do so because the Static Exception would then be raised under a local abstraction, which is not allowed.

Conclusion

I believe that Static Exceptions would be a useful addition to the language. They can make some code more readable and/or more efficient, and the cost required to extend the language is rather small. I’m interested to hear the opinion of the community about this feature.

[Edit 2013-01-14:] An interesting discussion about this post, on reddit.