© Thomas Mailund 2017

Thomas Mailund, Metaprogramming in R, 10.1007/978-1-4842-2881-4_4

4. Manipulating Expressions

Thomas Mailund

(1)Aarhus N, Denmark

Expressions, the kind you create using the quote function , come in four flavors: a primitive value, a name, a function call or a control structure, and a pairlist. Function calls include operators such as the arithmetic or logical operators because these are function calls as well in R, and control structures can be considered just a special kind of function calls—they only really differ from function calls in the syntax you use to invoke them.

class(quote(1))
## [1] "numeric"
class(quote("foo"))
## [1] "character"
class(quote(TRUE))
## [1] "logical"
class(quote(x))
## [1] "name"
class(quote(f(x)))
## [1] "call"
class(quote(2+2))
## [1] "call"
class(quote(if (TRUE) "foo" else "bar"))
## [1] "if"
class(quote(for (x in 1:3) x))
## [1] "for"

Of these, the calls and control structures are of course the more interesting; values and symbols are pretty simple, and you cannot do a lot with them. Pairlists are used for dealing with function parameters, so unless you are working with function arguments, you won’t see them in expressions. Calls and control structures, on the other hand, capture the action in an expression; you can treat these as lists, and you can thus examine them and modify them.1 Working with expressions this way is, I believe, the simplest approach and is the topic of this chapter. Substituting values for variables is another, complementary way that is the topic of the next chapter.

After you have learned the basics of expressions in the next section, the rest of the chapter will go through some potential real-life examples of how you would use metaprogramming. You can find a full version of the examples in the dfdr package in the book’s downloadable source code, available via www.apress.com/9781484228807 .

The Basics of Expressions

Both function calls and control structures can be manipulated as lists. Of those two, I will mostly focus on calls since those are, in my experience, more likely to be modified in a program. So, let’s get control structures out of the way first. I will describe only if and for; the rest are similar.

Accessing and Manipulating Control Structures

Statements involving control structures are expressions like any other expressions in R, and you can create an unevaluated version of them using quote. As I explained earlier, you can then treat this expression object as a list. So, you can get the length of the object, and you can get access to the elements in the object. For a single if statement, you get expressions of length 3, while for if-else statements, you get expressions of length 4. The first element is the name if. For all control structures and function calls, the first element will always be the name of the function, so if you think of control structures as just functions with a slightly weird syntax, you don’t have to consider them a special case at all.2 The second element is the test condition in the if statement, and after that, you get the body of the statement. If it is an if-else statement, the fourth element is the else part of the expression.

x <- quote(if (foo) bar)                                                                                          
length(x)
## [1] 3
x[[1]]
## `if`
x[[2]]
## foo
x[[3]]
## bar
y <- quote(if (foo) bar else baz)
length(y)
## [1] 4
y[[1]]
## `if`
y[[2]]
## foo
y[[3]]
## bar
y[[4]]
## baz

With for loops you get an expression of length 4 where the first element is, which is, of course, the name for. The second is the iteration variable, the third is the expression you iterate over, and the fourth is the loop body.

z <- quote(for (x in 1:4) print(x))
length(z)
## [1] 4
z[[1]]
## `for`
z[[2]]
## x
z[[3]]
## 1:4
z[[4]]
## print(x)

You can evaluate these control structures like any other expression.

eval(z)
## [1] 1
## [1] 2
## [1] 3
## [1] 4

You can modify them by assigning values to their components to change their behavior before you evaluate them. Here’s an example of changing what you loop over:

z[[3]] <- 1:2
eval(z)
## [1] 1
## [1] 2

Here’s an example of changing what you do in the function body:

z[[4]] <- quote(print(x + 2))
eval(z)
## [1] 3
## [1] 4

Here’s an example of changing the index variable and the body:

z[[2]] <- quote(y)
z[[4]] <- quote(print(y))
eval(z)
## [1] 1
## [1] 2

Accessing and Manipulating Function Calls

For function calls, their class is call, and when you treat them as lists, the first element is the name of the function being called, and the remaining elements are the function call arguments.

x <- quote(f(x,y,z))
class(x)
## [1] "call"
length(x)
## [1] 4
x[[1]]
## f
x[[2]]
## x
x[[3]]
## y
x[[4]]
## z

You can test whether an expression is a function call using the is.call function.

is.call(quote(x))
## [1] FALSE
is.call(quote(f(x)))
## [1] TRUE

You don’t have access to any function body or environment or anything like that here. This is just the name of a function; it is not until you evaluate the expression that you will have to associate the name with an actual function. You can, of course, always evaluate the function call using eval, and you can modify the expression if you want to change how it should be evaluated.

x <- quote(sin(2))                                                                                          
eval(x)
## [1] 0.9092974
x[[1]] <- quote(cos)
eval(x)
## [1] -0.4161468
x[[2]] <- 0
eval(x)
## [1] 1

Note that I didn’t quote the zero in the last assignment; I didn’t have to since numeric values are already expressions and do not need to be quoted.

To explore an expression, you usually need a recursive function. The two basic cases in a recursion are is.atomic (for values) and is.name (for symbols), and the recursive cases are is.call for function calls and is.pairlist if you want to deal with those. In the following function, which just prints the structure of an expression (I did not handle the case where the expression is a pairlist in this function):

f <- function(expr, indent = "") {
  if (is.atomic(expr) || is.name(expr)) { # basic case
    print(paste0(indent, expr))


  } else if (is.call(expr)) { # a function call / subexpression
    print(paste0(indent, expr[[1]]))
    n <- length(expr)
    if (n > 1) {
      new_indent <- paste0(indent, "  ")
      for (i in 2:n) {
        f(expr[[i]], new_indent)
      }
    }


  } else {
    print(paste0(indent, "Unexpected expression: ", expr[[1]]))
  }
}


f(quote(2 + 3*(x + y)))
## [1] "+"
## [1] "  2"
## [1] "  *"
## [1] "    3"
## [1] "    ("
## [1] "      +"
## [1] "        x"
## [1] "        y"

You might find the output here a little odd, but it captures the structure of the expression 2+3*(x+y). The outermost function call is the function +, and it has two arguments: 2 and the call to *. The call to * also has two arguments—naturally—where one is 3 and the other is a call to the function (. If you find this odd, then welcome to the club, but parentheses are functions in R. The call to ( has only a single argument, which happens to be a function call to + with the arguments x and y.

This is all there is to the direct manipulation of function calls, but of course, there is much that can be done with these simple tools. The following sections will show how you can use them to achieve powerful effects.

Expression Simplification

To see the manipulation of expressions in action, let’s consider a scenario where you want to simplify an expression. Say you want to evaluate subexpressions that you can immediately evaluate because they consist only of atomic values where you do not depend on variables, and you want to reduce multiplication by 1 or addition by 0. It looks something like this:

simplify_expr(quote(2*(0 + ((4 + 5)*x)*1)))
## 2 * (9 * x)

This isn’t quite perfect; if you really reduced the expression, you would see that you could rearrange the parentheses and multiply 2 by 9, but you are going to simplify expressions locally and not attempt to rewrite them here.

Since you are dealing with expressions, you need a recursive function that handles the basic cases (atomic values and names) and the recursive cases (calls and pairlists). You don’t expect to see a pairlist in an expression, so you simply give up if you see anything except atomic, name, or call objects. If you see any basic case, you just return that; you can’t simplify those further. For call objects, you call a function, simplify_call, which is responsible for handling calls .

simplify_expr <- function(expr) {
  if (is.atomic(expr) || is.name(expr)) {
    expr


  } else if (is.call(expr)) {
    simplify_call(expr)


  } else {
    stop(paste0("Unexpected expression ",
                deparse(expr),
                " in simplifying"))
  }
}

For call simplification, I don’t attempt to simplify function calls. I don’t know what any generic function is doing, so there is little I can do to simplify expressions that involve functions. I will assume, though, that if I am simplifying an expression, then functions in it behave as if they had call-by-value semantics and simplify their arguments. This is an assumption. It might be wrong, but for this exercises, you can assume it. So for general function calls, I will just simplify their arguments. For arithmetic expressions, I will try to simplify those further. I could also attempt to do that for other operations, but handling just the arithmetic operators shows how you would handle operators in sufficient detail that I trust you, dear reader, to be able to handle other operators if you need to do so.

Call handling can then look like this:

simplify_call <- function(expr) {
  if (expr[[1]] == as.name("+"))
    return(simplify_addition(expr[[2]], expr[[3]]))
  if (expr[[1]] == as.name("-")) {
    if (length(expr) == 2)
      return(simplify_unary_subtraction(expr[[2]]))
    else
      return(simplify_subtraction(expr[[2]], expr[[3]]))
  }


  if (expr[[1]] == as.name("*"))
    return(simplify_multiplication(expr[[2]], expr[[3]]))
  if (expr[[1]] == as.name("/"))
    return(simplify_division(expr[[2]], expr[[3]]))


  if (expr[[1]] == as.name("^"))
    return(simplify_exponentiation(expr[[2]], expr[[3]]))


  if (expr[[1]] == as.name("(")) {
    subexpr <- simplify_expr(expr[[2]])
    if (is.atomic(subexpr) || is.name(subexpr))
      return(subexpr)
    else if (is.call(subexpr) && subexpr[[1]] == as.name("("))
      return(subexpr)
    else
      return(call("(", subexpr))
  }


  simplify_function_call(expr)
}

This code is mostly self-explanatory, but a few comments are in order: First, you need to compare the call names with name objects. They are not actually character strings but have the type name; thus, you need to use as.name. Second, the minus comes in two flavors: binary subtraction and unary negation. You can tell the two apart by checking whether the call has one or two arguments (i.e., whether it has length 2 or 3; remember that the first element is the call name), and you just use two different functions to handle the two cases. Third, parentheses are also calls, so you need to handle them. You just get hold of the expression inside the parentheses. If this is something that doesn’t need parentheses (single values, names, or an expression already surrounded by parentheses), you just return that subexpression. Otherwise, you put parentheses around it. Finally, if you don’t know what else to do, you just treat the expression as a function call .

Now you just handle each operator in turn. They are all handled similarly, only differing in what you can simplify given each operator. For addition, you can get rid of addition by 0, and if both your arguments are numbers, you can evaluate them right away. Otherwise, you need to return a call to + with simplified operands.

simplify_addition <- function(f, g) {
  left <- simplify_expr(f)
  right <- simplify_expr(g)
  if (left == 0) return(right)
  if (right == 0) return(left)
  if (is.numeric(left) && is.numeric(right))
    return(left + right)
  call("+", left, right)
}

You can evaluate unary minus if its argument is numeric. Otherwise, you can get rid of an existing minus in the argument since two minuses make a plus, and if all else fails, you just have to return the simplified expression with a minus in front of it.

simplify_unary_subtraction <- function(f) {
   simplified <- simplify_expr(f)
   if (is.numeric(simplified))
     -simplified
   else if (is.call(simplified) && simplified[[1]] == "-")
     simplified[[2]]
   else
     bquote(-.(simplified))
}

For the final case here, you will use the function bquote. It works like quote but substitutes a value in where you put .(...). So, you essentially write quote(-simplified) except that you put the simplified expression inside the expression.

Binary subtraction is similar to addition but with a little more work when you subtract from 0. Here you need to use bquote again:

simplify_subtraction <- function(f, g) {
  left <- simplify_expr(f)
  right <- simplify_expr(g)
  if (left == 0) {
    if (is.numeric(right))
      return(-right)
    else
      return(bquote(-.(right)))
  }
  if (right == 0)
    return(left)
  if (is.numeric(left) && is.numeric(right))
    return(left - right)
  call("-", left, right)
}

For multiplication, you can simplify cases where the multiplication involves 0 or 1, but otherwise, the function looks similar to what you have seen before.

simplify_multiplication <- function(f, g) {
  left <- simplify_expr(f)
  right <- simplify_expr(g)
  if (left == 0 || right == 0)
    return(0)
  if (left == 1)
    return(right)
  if (right == 1)
    return(left)
  if (is.numeric(left) && is.numeric(right))
    return(left * right)
  call("*", left, right)
}

Division and exportation are just more of the same, with different cases to handle.

simplify_division <- function(f, g) {
  left <- simplify_expr(f)
  right <- simplify_expr(g)
  if (right == 1)
    return(left)
  if (is.numeric(left) && is.numeric(right))
    return(left / right)
  call("/", left, right)
}


simplify_exponentiation <- function(f, g) {
  left <- simplify_expr(f)
  right <- simplify_expr(g)
  if (right == 0) return(1)
  if (left == 0) return(0)
  if (left == 1) return(1)
  if (right == 1) return(left)
  if (is.numeric(left) && is.numeric(right))
    return(left ^ right)
  call("^", left, right)
}

The final function you need is a function-call simplification. Here you just have to simplify all the function’s arguments before returning a call. You can collect the arguments in a list and create a function call with an expression like this:

do.call("call", c(list(function_name), arguments))

This would take the arguments , as a list, and turn them into arguments in a call to call. This will work fine if the function_name value is a function name, but expressions such as f(x,y)(z) are also function calls; here the function name is f(x,y), and the argument is z. You cannot wrap such an expression up in a call to call, but you can just take a list and turn it into a call using as.call.

simplify_function_call <- function(expr) {
  function_name <- expr[[1]]
  arguments <- vector("list", length(expr) - 1)
  for (i in seq_along(arguments)) {
    arguments[i] <- list(simplify_expr(expr[[i + 1]]))
  }
  as.call(c(list(function_name), arguments))
}

For the same reason, you have to remedy the simplify_call function . There, you compare expr[[1]] with names to dispatch to the various arithmetic operators. This works only if expr[[1]] is a name, so you have to make sure that you make these comparisons only when it is a name.

simplify_call <- function(expr) {
  if (is.name(expr[[1]])) {
    # Dispatch to operators...
  }


  simplify_function_call(expr)
}

You could also get a little more ambitious and try to evaluate functions when all their arguments are values and when you know what the functions are—or at least have a reasonable expectation that you would know. You could always check whether you can find the name in a relevant environment and whether it is a function, but since you are simplifying expressions where you don’t expect to know variables that are not functions, it is probably too much to demand that all function symbols are known. Still, you could say that functions such as sin and cos and such as exp and log are their usual selves and then do something like this:

simplify_function_call <- function(expr) {
  function_name <- expr[[1]]
  arguments <- vector("list", length(expr) - 1)
  for (i in seq_along(arguments)) {
    arguments[i] <- list(simplify_expr(expr[[i + 1]]))
  }


  if (all(unlist(Map(is.numeric, arguments)))) {
    if (as.character(function_name) %in%
                c("sin", "cos", "exp", "log")) {
      result <- do.call(as.character(function_name), arguments)
      return(result)
    }
  }
  as.call(c(list(function_name), arguments))
}

You now have a simple program that lets you simplify expressions to a certain extent.

simplify_expr(quote(2*(0 + ((4 + 5)*x)*1)))
## 2 * (9 * x)

Neither function-call solution can handle named arguments. You simply work with positional arguments and just throw away the name information.

f <- function(x, y) x
expr1 <- quote(f(x = 2, y = 1))
expr2 <- quote(f(y = 2, x = 1))
eval(expr1)
## [1] 2
eval(expr2)
## [1] 1
simplify_expr(expr1)
## f(2, 1)
simplify_expr(expr2)
## f(2, 1)
eval(simplify_expr(expr1))
## [1] 2
eval(simplify_expr(expr2))
## [1] 2

It isn’t hard to remedy this, though. There is nothing special needed to work with named arguments when you deal with function calls; they are just accessed with the named function .

names(expr1)
## [1] ""  "x" "y"
names(expr2)
## [1] ""  "y" "x"

If you make sure that the result of your simplification gets the same name as the original expression, you will be OK.

simplify_function_call <- function(expr) {
  function_name <- expr[[1]]
  arguments <- vector("list", length(expr) - 1)
  for (i in seq_along(arguments)) {
    arguments[i] <- list(simplify_expr(expr[[i + 1]]))
  }
  result <- as.call(c(list(function_name), arguments))
  names(result) <- names(expr)
  result
}
simplify_expr(expr1)
## f(x = 2, y = 1)
simplify_expr(expr2)
## f(y = 2, x = 1)
eval(simplify_expr(expr1))
## [1] 2
eval(simplify_expr(expr2))
## [1] 1

Automatic Differentiation

As a second and only slightly more involved example, let’s consider automatic differentiation, which means automatically translating a function that computes an expression into a function that calculates the derived expression. I will assume that you have a function whose body contains only a single expression—one that doesn’t involve control structures or sequences of statements but just a single arithmetic expression—and recurse through this expression, applying the rules of differentiation. Although what you do with this metaprogram is more complicated than the expression simplification just implemented, you will see that the form of the program is similar.

You start with the main function, which you name d for differentiation. It takes two arguments: the function to be differentiated and the variable to take the derivative on. If you want the function to be able to handle the built-in mathematical functions, you need to handle these as special cases. These are implemented as so-called primitive functions and do not have a body. You need to handle them explicitly in the d function. For all other functions, you just need to compute the derivative of the expression in the function body. If you want to return a new function for the derivative, you can just take the function you are modifying and replace its body. Since R doesn’t let you modify arguments to a function, this will just create a copy you can return and leave the original function intact. Reusing the argument this way makes sure that the new function has the same arguments, with the same names and same default values, as the original. It also ensures that the derivative will have the same enclosing environment as the original function, which is potentially important for when you evaluate it.

The d function can look like this, where I’ve handled only three of the primitive functions—you can add the remaining as an exercise:

d <- function(f, x) {
  if (is.null(body(f))) {
    if (identical(f, sin)) return(cos)
    if (identical(f, cos)) return(function(x) -sin(x))
    if (identical(f, exp)) return(exp)


    stop("unknown primitive")

  } else {
    df <- f
    e <- environment(f)
    body(df) <- simplify_expr(diff_expr(body(f), x, e))
    df
  }
}

You send the function environment along with the recursion because you will need it when you have to deal with function calls later. There, you will need to look up functions and analyze which parameters they take to apply the chain rule. For now, you just pass it along in the recursion.

For aesthetic reasons , you simplify the expression you get from differentiating the body of f, using the code you wrote in the previous section. You can use d like this:

f <- function(x) x^2 + sin(x)
df <- d(f, "x")
df
## function (x)
## 2 * x + cos(x)

For computing the derivative of the function body, you follow the pattern you used for the expression simplification: you write a recursive function for dealing with expressions, where you dispatch function calls to different cases for the different arithmetic operations.

The two basic cases for the recursive function are numbers and names. Let’s assume that you do not get other atomic values such as logical vectors; you wouldn’t know how to differentiate them anyway. For numbers, the derivative is always 0, while for names it depends on whether you have the variable you are computing the derivative on or another variable. The recursive case for the function is function calls, where you just call another function to handle that case.

diff_expr <- function(expr, x, e) {
  if (is.numeric(expr)) {
    quote(0)


  } else if (is.name(expr)) {
    if (expr == x) quote(1)
    else quote(0)


  } else if (is.call(expr)) {
    diff_call(expr, x, e)


  } else {
    stop(paste0("Unexpected expression ",
                deparse(expr), " in parsing."))
  }
}

For calls, you dispatch based on the type of call; therefore, you deal with arithmetic expressions through a function for each operator, and you deal with parentheses similar to how you handled them in the expression simplification and when differentiating other function calls. You have to handle primitive functions and user-defined functions as two separate cases here as well. For user-defined functions, you can analyze them, figure out their formal arguments, and apply the chain rule. For primitive functions, formals will give you an empty list, so that strategy will not work for those. So, you handle them as a special case. I assume, here, that you have a list of names of the primitive functions. For example, you could have this if you need to handle only those three cases:

.built_in_functions <- c("sin", "cos", "exp")

Extend it as needed.

The function-handling calls look like this:

diff_call <- function(expr, x, e) {
  if (is.name(expr[[1]])) {
    if (expr[[1]] == as.name("+"))
      return(diff_addition(expr[[2]], expr[[3]], x, e))


    if (expr[[1]] == as.name("-")) {
      if (length(expr) == 2)
        return(call("-", diff_expr(expr[[2]], x, e)))
      else
        return(diff_subtraction(expr[[2]], expr[[3]], x, e))
    }


    if (expr[[1]] == as.name("*"))
      return(diff_multiplication(expr[[2]], expr[[3]], x, e))
    if (expr[[1]] == as.name("/"))
      return(diff_division(expr[[2]], expr[[3]], x, e))


    if (expr[[1]] == as.name("^"))
      return(diff_exponentiation(expr[[2]], expr[[3]], x, e))


    if (expr[[1]] == as.name("(")) {
      subexpr <- diff_expr(expr[[2]], x, e)
      if (is.atomic(subexpr) || is.name(subexpr))
        return(subexpr)
      else if (is.call(subexpr) && subexpr[[1]] == as.name("("))
        return(subexpr)
      else
        return(call("(", subexpr))
    }
  }


  if (is.name(expr[[1]]) &&
      as.character(expr[[1]]) %in% .built_in_functions)
    return(diff_built_in_function_call(expr, x, e))
  else
    return(diff_general_function_call(expr, x, e))
}

You handle the arithmetic operations just by following the rules you learned in calculus class.

diff_addition <- function(f, g, x, e) {
  call("+", diff_expr(f, x, e), diff_expr(g, x, e))
}


diff_subtraction <- function(f, g, x, e) {
  call("-", diff_expr(f, x, e), diff_expr(g, x, e))
}


diff_multiplication <- function(f, g, x, e) {
  # f' g + f g'
  call("+",
       call("*", diff_expr(f, x, e), g),
       call("*", f, diff_expr(g, x, e)))
}


diff_division <- function(f, g, x, e) {
  # (f' g − f g' )/g**2
  call("/",
       call("-",
        call("*", diff_expr(f, x, e), g),
        call("*", f, diff_expr(g, x, e))),
       call("^", g, 2))
}

diff_exponentiation <- function(f, g, x, e) {
  # Using the chain rule to handle this generally.
  dydf <- call("*", g,
               call("^", f, substitute(n - 1, list(n = g))))
  dfdx <- diff_expr(f, x, e)
  call("*", dydf, dfdx)
}

For function calls, you have to apply the chain rule. For primitive functions you cannot get a list of formal arguments, so you cannot handle these by inspecting the functions; you have to use their names to figure out what their arguments and derivatives are. I’m showing a few cases here, but I will leave handling other functions as an exercise for you:

diff_built_in_function_call <- function(expr, x, e) {
  # chain rule with a known function to differentiate...
  if (expr[[1]] == as.name("sin"))
    return(call("*", call("cos", expr[[2]]),
                diff_expr(expr[[2]], x, e)))


  if (expr[[1]] == as.name("cos"))
    return(call("*", call("-", call("sin", expr[[2]])),
                diff_expr(expr[[2]], x, e)))


  if (expr[[1]] == as.name("exp"))
    return(call("*", call("exp", expr[[2]]),
                diff_expr(expr[[2]], x, e)))
}

For other function calls, you can inspect the function to work out which variables it has and apply the chain rules to those variables. This works only if you can figure out which function you are referring to, so you cannot handle cases where you have to compute the function. In those cases, you just give up. If you have a symbol for the function, however, you can look it up and inspect it. This isn’t entirely safe for general use. If you calculate the derivative of a function and then change a global function that it refers to, you will have a derivative that uses the old global function, while the actual function uses the new global function. There isn’t much you can do about this, though. At the point where you apply the chain rule, you need to know which arguments the function takes. That means you need to know which function you are working with.

You can assume that the arguments used in the function call are the relevant ones to consider when you apply the chain rules. Those that you are not passing along in the function call will have default values and will not depend on the arguments given to the derivative function so that you can ignore them. Therefore, you can take the arguments in the function call and sum over those in the chain rule. You need to know the names of the arguments to compute the derivatives of the function, and you need to handle both positional and named arguments, and this is where you have to look up the actual function.

In the environment you have passed along in the recursion—the environment of the original function you are computing the derivative of—you look up the function you have to apply the chain rule to. With that function in hand, you can use the function match.call to get all the names of the arguments in the function call. The match.call function takes care of merging named and positional arguments. For each argument, you build a function call by changing the function to its derivative to the appropriate variable. You use the bquote function to call d to compute these derivatives. You then multiply the function call with the argument differentiated with the original variable. Collecting all these terms in a sum completes the chain rule.

diff_general_function_call <- function(expr, x, e) {
  function_name <- expr[[1]]
  if (!is.name(function_name))
    stop(paste0("Unexpected call ", deparse(expr)))


  func <- get(as.character(function_name), e)
  full_call <- match.call(func, expr)
  variables <- names(full_call)


  arguments <- vector("list", length(full_call) - 1)
  for (i in seq_along(arguments)) {
    var <- variables[i + 1]
    dfdz <- full_call
    dfdz[[1]] <- bquote(d(.(function_name), .(var)))
    dzdx <- diff_expr(expr[[i + 1]], x, e)
    arguments[[i]] <- bquote(.(dfdz) * .(dzdx))
  }
  as.call(c(list(sum), arguments))
}

There is one caveat with this solution: even if the original function is vectorized, the derivative won’t be. If you define the following functions, then g and h should be the same functions:

f <- function(x, y) x^2 * y
g <- function(z) f(2*z, z^2)
h <- function(z) 4*z^4

However, if you calculate d(g,"z") and d(h,"z") and call them with a vector of values, the former will add all the results together, while the latter will return a vector of values. The sum call in the derivative of g will gobble up all the values. You can fix this by calling Vectorize on d(g,"z").

Other than that, you now have a metaprogram for translating a function into its derivative. It doesn’t handle all possible functions; they have to be functions that evaluate simple expressions. The chain rule can be applied only to known functions mentioned by name, and you have handled only some of the primitive functions, but I trust you can see how you could build more functionality on top of what you have now.

Footnotes

1 To the extent that you can modify data in R. You are of course creating new objects with replacement operators.

2 They basically are just special cases of calls. The is.call function will return TRUE for them, and there is no difference in how you can treat them. The only difference is in the syntax for how you write control-structure expressions compared to function calls.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset
3.15.214.155