[Rd] R-3.3.3/R-3.4.0 change in sys.call(sys.parent())

Deepayan Sarkar deepayan.sarkar at gmail.com
Thu May 11 10:09:58 CEST 2017


On Wed, May 10, 2017 at 2:36 AM, William Dunlap via R-devel
<r-devel at r-project.org> wrote:
> Some formula methods for S3 generic functions use the idiom
>     returnValue$call <- sys.call(sys.parent())
> to show how to recreate the returned object or to use as a label on a
> plot.  It is often followed by
>      returnValue$call[[1]] <- quote(myName)
> E.g., I see it in packages "latticeExtra" and "leaps", and I suspect it
> used in "lattice" as well.
>
> This idiom has not done good things for quite a while (ever?) but I noticed
> while running tests that it acts differently in R-3.4.0 than in R-3.3.3.
> Neither the old or new behavior is nice.  E.g., in R-3.3.3 we get
>
>> parseEval <- function(text, envir) eval(parse(text=text), envir=envir)
>> parseEval('lattice::xyplot(mpg~hp, data=datasets::mtcars)$call',
> envir=new.env())
> xyplot(expr, envir, enclos)
>
> and
>
>> evalInEnvir <- function(call, envir) eval(call, envir=envir)
>> evalInEnvir(quote(lattice::xyplot(mpg~hp, data=datasets::mtcars)$call),
> envir=new.env())
> xyplot(expr, envir, enclos)
>
> while in R-3.4.0 we get
>> parseEval <- function(text, envir) eval(parse(text=text), envir=envir)
>> parseEval('lattice::xyplot(mpg~hp, data=datasets::mtcars)$call',
> envir=new.env())
> xyplot(parse(text = text), envir = envir)
>
> and
>
>> evalInEnvir <- function(call, envir) eval(call, envir=envir)
>> evalInEnvir(quote(lattice::xyplot(mpg~hp, data=datasets::mtcars)$call),
> envir=new.env())
> xyplot(call, envir = envir)
>
> Should these packages be be fixed up to use just sys.call()?

I admit to not understanding these things very well, but I'll try to
explain why I ended up with the usage I have. The main use of the
$call component within lattice is to use it in the summary method, as
in:

> summary(xyplot(mpg~hp, data=mtcars))

Call:
xyplot(mpg ~ hp, data = mtcars)

Number of observations:
[1] 32

Here is a minimal approximation to what I need: Here foo() and bar()
are generics producing objects of class "foobar", bar() calls foo()
with one argument changed, and the print() method for "foobar" is just
supposed to print the call that produced it:

########

foo <- function(x, ...) UseMethod("foo")
bar <- function(x, ...) UseMethod("bar")
print.foobar <- function(x, ...) print(x$call)

## Using plain sys.call():

foo.formula <- function(x, ...)
{
    ans <- structure(list(), class = "foobar")
    ans$call <- sys.call()
    ans
}

bar.formula <- function(x, ..., panel)
{
    foo.formula(x, ..., panel = panel.bar)
}

foo.table <- function(x, ...)
{
    ans <- foo.formula(Freq ~ Var1,
                       as.data.frame.table(x), ...)
    ans
}

## I would get

foo(y ~ x)
# foo.formula(y ~ x)

bar(y ~ x)
# foo.formula(x, ..., panel = panel.bar)

foo(as.table(1:10))
# foo.formula(Freq ~ Var1, as.data.frame.table(x), ...)

## The last two are improved by

foo.formula <- function(x, ...)
{
    ans <- structure(list(), class = "foobar")
    ans$call <- sys.call(sys.parent())
    ans
}

bar(y ~ x)
## bar.formula(y ~ x)

foo(as.table(1:10))
## foo.table(as.table(1:10))

########

Adding

ans$call[[1]] <- quote(foo)

(or quote(bar) in bar.formula) is needed to replace the unexported
method name (foo.formula) with the generic name (foo), but that's
probably not the problem.

With this approach in lattice,

p <- some.function(...)
eval(p$call)

usually works, but not always, if I remember correctly.

I'm happy to consider more robust solutions. Maybe I just need to have a

...$call <- sys.call()

statement in every method?

-Deepayan



More information about the R-devel mailing list