[R] Wrong environment when evaluating and expression?
William Dunlap
wdunlap at tibco.com
Tue Jul 5 20:48:52 CEST 2011
> -----Original Message-----
> From: r-help-bounces at r-project.org
> [mailto:r-help-bounces at r-project.org] On Behalf Of Joshua Wiley
> Sent: Monday, July 04, 2011 1:12 AM
> To: r-help at r-project.org
> Subject: [R] Wrong environment when evaluating and expression?
>
> Hi All,
>
> I have constructed two expressions (e1 & e2). I can see that they are
> not identical, but I cannot figure out how they differ.
>
> ###############
> dat <- mtcars
> e1 <- expression(with(data = dat, lm(mpg ~ hp)))
> e2 <- as.expression(substitute(with(data = dat, lm(f)),
> list(f = mpg ~ hp)))
>
> str(e1)
> str(e2)
> all.equal(e1, e2)
> identical(e1, e2) # false
With the appended str.language function you can see the difference
between e1 and e2. It displays
`name` class(length)
of each component of a recursive object, along with a short text summary
of
it after a colon.
> str.language(e1)
`e1` expression(1): expression(with(data = da...
`` call(3): with(data = dat, lm(mpg ~...
`` name(1): with
`data` name(1): dat
`` call(2): lm(mpg ~ hp)
`` name(1): lm
`` call(3): mpg ~ hp
`` name(1): ~
`` name(1): mpg
`` name(1): hp
> str.language(e2)
`e2` expression(1): expression(with(data = da...
`` call(3): with(data = dat, lm(mpg ~...
`` name(1): with
`data` name(1): dat
`` call(2): lm(mpg ~ hp)
`` name(1): lm
`` formula(3): mpg ~ hp
`` name(1): ~
`` name(1): mpg
`` name(1): hp
`Attributes of ` list(2): structure(list(class = "f...
`class` character(1): "formula"
`.Environment` environment(5): <R_GlobalEnv> dat e1 e2 s...
It is a bug in all.equal() that it ignores attributes of formulae.
E.g.,
> all.equal(y~x, terms(y~x))
[1] TRUE
> identical(y~x, terms(y~x))
[1] FALSE
Here is str.language
str.language <-
function (object, ..., level = 0, name = deparse(substitute(object)),
attributes = TRUE)
{
abbr <- function(string, maxlen = 25) {
if (length(string) > 1 || nchar(string) > maxlen)
paste(substring(string[1], 1, maxlen), "...", sep = "")
else string
}
myDeparse <- function(object) {
if (!is.environment(object)) {
deparse(object)
}
else {
ename <- environmentName(object)
if (ename == "")
ename <- "<unnamed env>"
paste(sep = "", "<", ename, "> ", paste(collapse = " ",
objects(object)))
}
}
cat(rep(" ", level), sep = "")
if (is.null(name))
name <- ""
cat(sprintf("`%s` %s(%d): %s\n", abbr(name), class(object),
length(object), abbr(myDeparse(object))))
a <- attributes(object)
if (is.recursive(object) && !is.environment(object)) {
object <- as.list(object)
names <- names(object)
for (i in seq_along(object)) {
str.language(object[[i]], ..., level = level + 1,
name = names[i], attributes = attributes)
}
}
if (attributes) {
a$names <- NULL
if (length(a) > 0) {
str.language(a, level = level + 1, name = paste("Attributes
of",
abbr(name)), attributes = attributes)
}
}
}
Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com
>
> eval(e1)
> eval(e2)
> ################
>
> The context is trying to use a list of formulae to generate several
> models from a multiply imputed dataset. The package I am using (mice)
> has methods for with() and that is how I can (easily) get the pooled
> results. Passing the formula directly does not work, so I was trying
> to generate the entire call and evaluate it as if I had typed it at
> the console, but I am missing something (probably rather silly).
>
> Thanks,
>
> Josh
>
>
> --
> Joshua Wiley
> Ph.D. Student, Health Psychology
> University of California, Los Angeles
> http://www.joshuawiley.com/
>
> ______________________________________________
> R-help at r-project.org mailing list
> 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