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

Prof Brian Ripley ripley at stats.ox.ac.uk
Wed Jun 18 19:50:45 MEST 2003


Are you *sure* this is a bug, and not just how you would like it to be
to help with a misconception?

I can't see anything (including ?formula) which says that the formula
environment should be used, and I can think of quite a few situations
which this would break.  The idea of update.default is that it should be
the same as evaluating the revised call in the calling frame, and your
version doesn't do that.

On Wed, 18 Jun 2003 minka at stat.cmu.edu wrote:

> 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)  
## not needed, BTW
>   fit = make.model(Boston)
>   fit = update(fit,".~.-crim")
>   # Object "x" not found

Yes, and I think that is correct.  This sort of thing is often done to 
fit against a different x.

Note that you are not even appealing to ?formula correctly. It says

     A formula object has an associated environment, and this
     environment (rather than the parent environment) is used by
     `model.frame' to evaluate variables that are not found in the
     supplied `data' argument.

and x is not such a variable (it is the `data' argument).

Now, had you done

make.form <- function(formula, data)
{
    env <- new.env()
    for(i in names(data)) assign(i, data[[i]], envir=env)
    environment(formula) <- env
    formula
}
form <- make.form(medv~age+black+crim, Boston)
fit <- lm(form)
update(fit, .~.-crim)

you *would* be making good use of the environment of the formula, and it 
does work.  I am pretty sure that is what ?formula is saying can be done.


> 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
> }
> 
> ______________________________________________
> R-devel at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-devel
> 

-- 
Brian D. Ripley,                  ripley at stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272866 (PA)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595



More information about the R-devel mailing list