[R] Passing formula and weights error

William Dunlap wdun|@p @end|ng |rom t|bco@com
Fri Aug 28 18:38:07 CEST 2020


Note that neither call to glm in your myglm function really works -
the first one is using the 'weights' object from the global
environment, not the weights argument.  E.g., in the fresh R session,
where I avoid making unneeded assignments and use fixed x and y for
repeatability,

  > n <- 16
  > data <- data.frame(x = log2(1:n), y = 1:n)
  > myglm2 <- function(formula, data, weights)
      {
          glm(formula, data=data, family=gaussian(), weights=weights)
      }
  > myglm2(y~., data=data, weights=1/(1:n))
  Error in model.frame.default(formula = formula, data = data, weights
= weights,  :
    invalid type (closure) for variable '(weights)'

The error arises because glm finds stats::weights, a function, not the
argument called weights.  glm(), lm() and their ilk evaluate their
weights and subset arguments in the environment of the formula.  In
this case environment(y~.) is .GlobalEnv, not the function's
environment.  The following function gives one way to deal with this,
by giving formula a new environment that inherits from its original
environment and contains the extra variables.

  > myglm3 <- function(formula, data, weights)
      {
          envir <- list2env(list(weights=weights), parent=environment(formula))
          environment(formula) <- envir
          glm(formula, data=data, family=gaussian(), weights=weights)
      }
  > myglm3(y~., data=data, weights=1/(1:n))

  Call:  glm(formula = formula, family = gaussian(), data = data,
weights = weights)

  Coefficients:
  (Intercept)            x
     -0.09553      2.93352

  Degrees of Freedom: 15 Total (i.e. Null);  14 Residual
  Null Deviance:      60.28
  Residual Deviance: 7.72         AIC: 70.42

This is the same result you get with a direct call to
  glm(y~., data=data, weights=1/(1:n))

This is a common problem and I don't know if there is a FAQ on it or a
standard function to deal with it.

Bill Dunlap
TIBCO Software
wdunlap tibco.com

On Fri, Aug 28, 2020 at 8:33 AM John Smith <jswhct using gmail.com> wrote:
>
> Dear R-help:
>
> I am writing a function based on glm and would like some variations of
> weights. In the code below, I couldn't understand why the second glm
> function fails and don't know how to fix it:
>
> Error in eval(extras, data, env) : object 'newweights' not found
>  Calls: print ... eval -> <Anonymous> -> model.frame.default -> eval -> eval
>  Execution halted
>
> ### R code
> y <- rnorm(100)
>  x <- rnorm(100)
>  data <- data.frame(cbind(x, y))
>  weights <- rep(1, 100)
>  n <- 100
>  myglm <- function(formula, data, weights){
>      ## this works
>      print(glm(formula, data, family=gaussian(), weights))
>      ## this is not working
>      newweights <- rep(1, n)
>      glm(formula, data, family=gaussian(), weights=newweights)
>  }
>  myglm(y~., data, weights)
>
>         [[alternative HTML version deleted]]
>
> ______________________________________________
> R-help using r-project.org mailing list -- To UNSUBSCRIBE and more, see
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.



More information about the R-help mailing list