Skip to content

Instantly share code, notes, and snippets.

@egnha
Last active November 3, 2021 05:57
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save egnha/38222f4f4b933496ceb3488429760cbe to your computer and use it in GitHub Desktop.
Save egnha/38222f4f4b933496ceb3488429760cbe to your computer and use it in GitHub Desktop.
A short note on tail-call elimination via exception handling

A short note on tail-call elimination via exception handling

The basic mechanism of tail-call elimination is simple: when a procedure reaches a tail call, capture the transformed arguments and feed them back into the machinery of the procedure. Tail calls are thereby made iteratively; they do not accumulate on the call stack.

There is a folklore trick to implement this mechanism using exception handling: in place of a tail call, raise an exception containing the transformed arguments, then catch the exception in order to pass the arguments to a new call. This isn't quite the same as feeding the arguments back into the machinery of the procedure, because a new call is made (with the concomitant overhead of a new environment, etc.). But the previous call is nevertheless popped from the call stack, and thereby eliminated. I could not trace the source of this trick, but it is surely ancient, cf. Simmons–Beckman–Murphy (2010), Norvig (1992, Sec. 22.3), Marlin (1979, Sec. 2.4).

Let's see how this goes in R. Consider the recursive definition of the factorial function.

factorial <- function(n, accum = 1) {
  if(n == 0)
    return(accum)
  Recall(n - 1, accum * n)  # recursive call
}

Instead of invoking a recursive call, we want to raise an exception containing the transformed arguments. This means we should instead define factorial() like so,

factorial <- function(n, accum = 1) {
  if(n == 0)
    return(accum)
  recur(n - 1, accum * n)  # raise an exception
}

where recur() raises (signals) an ad hoc exception (condition) that simply contains the arguments:

recur <- function(...) {
  args <- list(...)
  class(args) <- c("recur", "condition")
  signalCondition(args)
}

The calling behavior of factorial() must now be able to catch the recur exception in order to pass it to the next invocation of factorial(). This amounts to applying the following function transformer to factorial().

recursively <- function(f) {
  function(...) {
    args <- list(...)
    while(TRUE)
      tryCatch(
        return(do.call(f, args)),
	recur = function(a) args <<- unclass(a)
      )
  }
}

It is evident that recursively() linearizes tail recursive calls. For example, you can compute the factorial of 1000 by recursion, without exceeding R's limit on call stack depth.

library(gmp)  # provides big integers

factorial <- recursively(
  function(n, accum = as.bigz(1)) {
    if(n == 0)
      return(accum)
    recur(n - 1, accum * n)
  }
)

factorial(1000)
#> Big Integer ('bigz') :
#> [1] 402387260077093773...000000000000000000 [2568 digits]

Comparison with Stirling's approximation gives confidence in the result.

stirling <- function(n) (n + .5)*log(n) - n + .5*log(2*pi)
stirling(1000) - log(factorial(1000))  # difference should be small
#> [1] -8.333333e-05

Of course, eliminating tail calls using high-level exception handling is costly. Proper tail-call elimination is done at a lower level of interpretation, or compilation, using gotos (see Sections 22.3 and 23.1 of Norvig). Dirk Schumacher shows us how this may be done in R by rewriting a function's bytecode.

Footnote — It would appear that the transformation recursively() would require any function that was previously written with Recall() to be rewritten with recur() in its place. However, this shortcoming is easily overcome by monkey patching the function environment to bind Recall to recur:

recursively <- function(f) {
  f_ <- f
  environment(f_) <- list2env(list(Recall = recur), parent = environment(f))
  # no change below, aside from renaming `f` to `f_`
  function(...) {
    args <- list(...)
    while(TRUE)
      tryCatch(
        return(do.call(f_, args)),
        recur = function(a) args <<- unclass(a)
      )
  }
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment