[Rd] update.default bugfix (PR#3288)

minka at stat.cmu.edu minka at stat.cmu.edu
Wed Jun 18 20:14:13 MEST 2003


According to the man page for formula, "a formula object has an associated
environment".  However, update.default doesn't use this environment, which
creates problems like the following:

  make.model <- function(x) { lm(medv~.,x) }
  library(MASS)
  data(Boston)
  fit = make.model(Boston)
  fit = update(fit,".~.-crim")
  # Object "x" not found

Here is a modification of update.default (from R 1.7.0) that fixes the
problem.

Tom

update.default <-
    function (object, formula., ..., evaluate = TRUE)
{
    call <- object$call
    if (is.null(call))
    stop("need an object with call component")
    extras <- match.call(expand.dots = FALSE)$...
    if (!missing(formula.))
    call$formula <- update.formula(formula(object), formula.)
    if(length(extras) > 0) {
    existing <- !is.na(match(names(extras), names(call)))
    ## do these individually to allow NULL to remove entries.
    for (a in names(extras)[existing]) call[[a]] <- extras[[a]]
    if(any(!existing)) {
        call <- c(as.list(call), extras[!existing])
	    call <- as.call(call)
	    }
    }
    if(evaluate) {
      # minka: use environment of formula instead of parent.frame
      # see the man page for formula
      env<-environment(call$formula)
      if (is.null(env)) env<-parent.frame()
      eval(call,env)
    }
    else call
}



More information about the R-devel mailing list