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

2017-05-12 Thread Deepayan Sarkar
On Thu, May 11, 2017 at 8:03 PM, William Dunlap  wrote:
> Here is a case where the current scheme fails:
>
>   > with(datasets::mtcars, xyplot(mpg~wt|gear)$call)
>   xyplot(substitute(expr), data, enclos = parent.frame())

Right, thanks. So I guess I can't avoid setting $call inside every method.

-Deepayan

> Bill Dunlap
> TIBCO Software
> wdunlap tibco.com
>
> On Thu, May 11, 2017 at 1:09 AM, Deepayan Sarkar 
> wrote:
>>
>> On Wed, May 10, 2017 at 2:36 AM, William Dunlap via R-devel
>>  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
>
>

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


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

2017-05-11 Thread William Dunlap via R-devel
Here is a case where the current scheme fails:

  > with(datasets::mtcars, xyplot(mpg~wt|gear)$call)
  xyplot(substitute(expr), data, enclos = parent.frame())


Bill Dunlap
TIBCO Software
wdunlap tibco.com

On Thu, May 11, 2017 at 1:09 AM, Deepayan Sarkar 
wrote:

> On Wed, May 10, 2017 at 2:36 AM, William Dunlap via R-devel
>  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
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


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

2017-05-11 Thread Deepayan Sarkar
On Wed, May 10, 2017 at 2:36 AM, William Dunlap via R-devel
 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

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


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

2017-05-10 Thread Tomas Kalibera


The difference in the outputs between 3.3 and 3.4 is in how call 
expressions are selected in presence of .Internals. R is asked for a 
call expression for "eval". In 3.3 one gets the arguments for the call 
expression from the .Internal that implements eval. In 3.4 one gets the 
arguments for the call expression from the closure wrapper of "eval", 
which is less surprising. See e.g.


(3.4)
> evalq()
Error in evalq() : argument is missing, with no default

vs

(3.3)
> evalq()
Error in eval(substitute(expr), envir, enclos) :
  argument is missing, with no default

(and yes, these examples work with sys.call() and lattice originally 
used it in xyplot - perhaps it'd be best to submit a bug report/issue 
for lattice)


Tomas


On 05/09/2017 11:06 PM, William Dunlap via R-devel 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()?

Bill Dunlap
TIBCO Software
wdunlap tibco.com

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel