[R] Using functions within functions (environment problems)

Prof Brian Ripley ripley at stats.ox.ac.uk
Fri Jan 26 13:12:06 CET 2007


I don't think your subject line is relevant.  You do not have 'functions 
within functions': lmerFrames is not within lmer.  (You seem to be 
confusing functions within and calls from.)

Your example does not work (did you test it?).  When the erroneous runif 
call is corrected (it gives a result of length 0), I get a different error 
about 'weights', and indeed you have not specified 'weights' nor 'subset' 
nor 'na.action' nor 'offset'.

The following does work for me:

lmerWrapper <- function(formula, data, ...)
{

     xNew <- runif(length(data[,1]))
     fNew <- sample(1:4, length(data[,1]), replace = TRUE)
     data <- as.data.frame(cbind(data, xNew, fNew))
     formula <- update(formula, .~. + xNew + (1|fNew))
     out <- lmer (formula = formula, data = data, ...)
}

dat <- data.frame(Y = rnorm(100), X1 = rnorm(100), X2 = rnorm(100),
         F1 = as.factor(sample(1:4, 400, replace = T)))
test <- lmerWrapper (Y ~ X1 + X2 + (1|F1), data = dat)

so whatever your actual problem is, it is it seems not about finding xNew.


There is one potential problem I spotted.  One of the places a standard 
model-fitting function will look for variables is in the environment of 
'formula'.  This is an argument, and update.formula changes the 
environment, so it is possible that old (rather than additional) variables 
could disappear from view.


On Fri, 26 Jan 2007, Colin Beale wrote:

> Hi everyone,
>
> I've been having difficulty writing wrapper functions for some
> functions where those same functions include other functions with
> eval()
> calls where the environment is specified. A very simple example using
> function lmer from lme4:
>
> lmerWrapper <- function(formula, data, family = gaussian, method =
> c("REML",
>    "ML", "PQL", "Laplace", "AGQ"), control = list(), start = NULL,
>    subset, weights, na.action, offset, contrasts = NULL, model =
> TRUE,
>
>    ...)
> {
>
>    xNew <- runif(0,1, length(data[,1]))
>    fNew <- sample(1:4, length(data[,1]), replace = T)
>    data <- as.data.frame(cbind(data, xNew, fNew))
>    formula <- update(formula, .~. + xNew + (1|fNew))
>    out <- lmer (formula = formula, data = data, family = family,
> method =
>        method, weights = weights, control = control, start = start,
>        subset = subset, na.action = na.action, offset = offset,
>        contrasts = contrasts, model = model)
> }
>
> dat <- data.frame(Y = rnorm(100), X1 = rnorm(100), X2 = rnorm(100),
>        F1 = as.factor(sample(1:4, 400, replace = T)))
> test <- lmerWrapper (Y ~ X1 + X2 + (1|F1), data = dat)
>
>
> This function attempts to create two new variables, add these to the
> data.frame and modify the formula for include these two new variables,
> and then fit this expanded model using lmer. Clearly the example is
> silly, but it illustrates the problem as it fails with the error:
>
> Error in eval(expr, envir, enclos) : object "xNew" not found
>
> because a function within lmer (lmerFrames) makes an eval call where
> the environment is specified as the .GlobalEnv which doesn't contain
> xNew - it needs to be looking in the environment from which it was
> called rather than going right back to the root. In a more general
> context, I might like to create a function where I don't specify a new
> data.frame in the wrapper, but want the function to search the back
> down
> the search path for each component, finding xNew in the environment of
> the wrapper function and X1 in the .GlobalEnv. Is there a general
> solution to this? Or do I need to create a modified lmer function that
> calls a modified lmerFrames function where I specify the environment
> differently? There's quite a lot in the archives dealing with
> environments and search paths, but I'm either not understanding how to
> apply the wisdom therein, or not finding the specific answer to my
> problem, and I should say that I have this problem with more than just
> the lmer function.
>
> Thanks for any pointers,
>
> Colin
>
>> sessionInfo()
> R version 2.4.1 (2006-12-18)
> i386-pc-mingw32
>
> locale:
> LC_COLLATE=English_United Kingdom.1252;LC_CTYPE=English_United
> Kingdom.1252;LC_MONETARY=English_United
> Kingdom.1252;LC_NUMERIC=C;LC_TIME=English_United Kingdom.1252
>
> attached base packages:
> [1] "stats"     "graphics"  "grDevices" "datasets"  "tcltk"
> "utils"
>    "methods"   "base"
>
> other attached packages:
>      debug    mvbutils        lme4      Matrix     lattice
> svSocket
>       svIO      R2HTML      svMisc       svIDE
>    "1.1.0"     "1.1.1" "0.9975-10"  "0.9975-8"   "0.14-16"
> "0.9-5"
>    "0.9-5"      "1.58"     "0.9-5"     "0.9-5"
>
>
>
>
> Dr. Colin Beale
> Spatial Ecologist
> The Macaulay Institute
> Craigiebuckler
> Aberdeen
> AB15 8QH
> UK
>
> Tel: 01224 498245 ext. 2427
> Fax: 01224 311556
> Email: c.beale at macaulay.ac.uk
>
>
>
>

-- 
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-help mailing list