[R] Why can't Anove (car package) see the data?

ripley@stats.ox.ac.uk ripley at stats.ox.ac.uk
Wed Aug 14 18:55:34 CEST 2002


It is indeed a scope problem.  Anova.glm is calling functions which call
update and so is not calling glm in the correct frame.

Here is a fix:

fun.2 <- function(df){
    mod <- eval(substitute(
               glm(partic != 'not.work' ~ hincome + children + region,
               data=df, family=binomial), list(df=df)))
    Anova(mod)
}

which makes sure the actual data object gets stored in the call component
of the fitted model.  That is often a good idea, but Anova.glm needs
correcting.

This is a notorious problem in S, and although in ca 1998 I rewrote R's
update to work better (and better than S's) there is no getting away from
the S/R scope rules:  functions which have been called en route to (here)
Anova.II.LR.glm are not searched.

I'll correspond directly with John about possible solutions.  It should be
possible to use drop1.glm, or at least its ideas.


On Wed, 14 Aug 2002, John Fox wrote:

> Dear Patrick,
>
> It's difficult for me to tell from your description what the specific
> nature of the problem is, though it seems to be some kind of scoping issue.
>
> I've experimented a bit and found that the call to update (indirectly) from
> Anova.glm (with LR type-II tests) seems to cause problems:
>
>      > fun.1 <- function(df){
>      +     mod <- glm(partic != 'not.work' ~ hincome + children + region,
>      +         data=df, family=binomial)
>      +     Anova(mod)
>      +     }
>      > fun.1(Womenlf)
>      Error in eval(expr, envir, enclos) : numeric envir arg not of length one
>      > traceback()
>      16: eval(predvars, data, env)
>      15: model.frame.default(formula = partic != "not.work" ~ children +
>              region, data = df, drop.unused.levels = TRUE)
>      14: model.frame(formula = partic != "not.work" ~ children + region,
>              data = df, drop.unused.levels = TRUE)
>      13: eval(expr, envir, enclos)
>      12: eval(mf, parent.frame())
>      11: glm(formula = partic != "not.work" ~ children + region, family =
> binomial,
>              data = df)
>      10: eval(expr, envir, enclos)
>      9: eval(call, parent.frame())
>      8: update.default(mod, eval(parse(text = paste(".~.-",
> paste(c(names[term],
>          rels), collapse = "-")))))
>      7: update(mod, eval(parse(text = paste(".~.-", paste(c(names[term],
>          rels), collapse = "-")))))
>      6: Anova.II.LR.glm(mod)
>      5: switch(test.statistic, LR = Anova.II.LR.glm(mod), Wald =
> Anova.II.Wald.glm(mod),
>          F = Anova.II.F.glm(mod, error, error.estimate))
>      4: switch(type, II = switch(test.statistic, LR = Anova.II.LR.glm(mod),
>          Wald = Anova.II.Wald.glm(mod), F = Anova.II.F.glm(mod, error,
>              error.estimate)), III = switch(test.statistic, LR =
> Anova.III.LR.glm(mod),
>          Wald = Anova.III.Wald.glm(mod), F = Anova.III.F.glm(mod,
>              error, error.estimate)))
>      3: Anova.glm(mod)
>      2: Anova(mod)
>      1: fun.1(Womenlf)
>
> (This uses the Womenlf data frame in the car package.)
>
> In contrast, Anova.lm, which doesn't call update, works OK:
>
>     > fun.2 <- function(df){
>      +     mod <- lm(prestige ~ income + education, data=df)
>      +     Anova(mod)
>      +     }
>      > fun.2(Prestige)
>      Anova Table (Type II tests)
>
>      Response: prestige
>              Sum Sq Df F value    Pr(>F)
>      income    2248.1  1  36.856 2.355e-08
>      education 8577.3  1 140.615 < 2.2e-16
>      Residuals 6038.9 99
>      >
>
> (using the Prestige data frame, again in car.)
>
> I don't see an immediate way around the problem, but I'll think about it.
> In addition, if you send me some more information -- the data that you were
> using, the model that you fit, the function from which you called Anova --
> I'll take a look a it. I'm leaving town for several days tomorrow. If you
> send me the information before then, I'll take it with me.
>
> I'm sorry that you're experiencing this problem,
>   John
>
> At 03:14 PM 8/14/2002 +1200, Patrick Connolly wrote:
> >At the end of the 'Details:' section of the help on Anova (car
> >package), it states:
> >
> >      The standard R `anova' function calculates sequential (type-I)
> >      tests. These rarely test meaningful hypotheses.
> >
> >So I thought I'd try it.  However, I was perplexed to get this
> >message:
> >
> >Browse[1]> Anova.glm(leaf.glm1, type ="II")
> >Error in terms.formula(formula, data = data) :
> >         Object "use.df" not found
> >
> >The regular anova function can find use.df.  What could make it
> >invisible to Anova?  I thought it might be because terms.formula took
> >an argument x and I already had an object x, but changing its name
> >didn't help.  I spent some time searching the archives but found no
> >mention of this problem.  I read some of the car package help files,
> >but didn't notice a reference to what is different in the way data is
> >seen.
> >
> >The example given in the help file does work, but it uses a data
> >object which is in the working directory.  That's not practicable
> >within a function.  So I'd appreciate other ideas.
> >
> >platform i686-pc-linux-gnu
> >arch     i686
> >os       linux-gnu
> >system   i686, linux-gnu
> >status
> >major    1
> >minor    5.1
> >year     2002
> >month    06
> >day      17
> >language R
> >
> >Thanks
> >
> >--
> >Patrick Connolly
> >HortResearch
> >Mt Albert
> >Auckland
> >New Zealand
> >Ph: +64-9 815 4200 x 7188
> >~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~
> >I have the world`s largest collection of seashells. I keep it on all
> >the beaches of the world ... Perhaps you`ve seen it.  ---Steven Wright
> >~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~.~
> >
> >
> >______________________________________________________
> >The contents of this e-mail are privileged and/or confidential to the
> >named recipient and are not to be used by any other person and/or
> >organisation. If you have received this e-mail in error, please notify
> >the sender and delete all material pertaining to this e-mail.
> >______________________________________________________
> >-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
> >r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
> >Send "info", "help", or "[un]subscribe"
> >(in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
> >_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._
>
> -----------------------------------------------------
> John Fox
> Department of Sociology
> McMaster University
> Hamilton, Ontario, Canada L8S 4M4
> email: jfox at mcmaster.ca
> phone: 905-525-9140x23604
> web: www.socsci.mcmaster.ca/jfox
> -----------------------------------------------------
>
> -.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
> r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
> Send "info", "help", or "[un]subscribe"
> (in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
> _._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._
>

-- 
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 272860 (secr)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595

-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._



More information about the R-help mailing list