[Rd] [R] converting result of substitute to 'ordidnary'expression
Matthew Dowle
mdowle at mdowle.plus.com
Mon Jun 28 16:36:29 CEST 2010
> ## this does work (thanks to the help page), but one needs to remember to
> call eval
> subset(dat, eval(subsetexp))
> Is there a way to create subsetexp that needs no eval inside the call to
> subset()?
Whats wrong with needing to call eval ? If I'm reading that code, and
someone else wrote it, or I wrote it a long time
ago, then I immediately know to look above that line for where subsetexp
gets its expression. I like seeing eval() as
it makes it clearer what the programmer intended.
Matthew
"Vadim Ogranovich" <vogranovich at jumptrading.com> wrote in message
news:22D850BC39A25742977325ADDE208E7702CB5CC1A0 at chiexchange02.w2k.jumptrading.com...
>I switched the thread to r-devel because here I am proposing a patch for
>subset.data.frame().
>
>
> Thank you Chuck, it was inspiring. It turns out that a simple modification
> to subset.data.frame makes my example work:
>
> subset.data.frame <-
> function (x, subset, select, drop = FALSE, ...)
> {
> if (missing(subset))
> r <- TRUE
> else {
> r <- eval(substitute(subset), x, parent.frame())
>
> if (!is.logical(r)) {
> ## try w/o substitute
> r <- eval(subset, x, parent.frame())
> }
>
> if (!is.logical(r))
> stop("'subset' must evaluate to logical")
>
> r <- r & !is.na(r)
> }
> if (missing(select))
> vars <- TRUE
> else {
> nl <- as.list(1L:ncol(x))
> names(nl) <- names(x)
> vars <- eval(substitute(select), nl, parent.frame())
> }
> x[r, vars, drop = drop]
> }
>
>
> And now:
>> dat <- data.frame(x=1:10, y=1:10)
>
>> subset(dat, 5<x)
> x y
> 6 6 6
> 7 7 7
> 8 8 8
> 9 9 9
> 10 10 10
>
>> subsetexp <- expression(5<x)
>
>> subset(dat, subsetexp)
> x y
> 6 6 6
> 7 7 7
> 8 8 8
> 9 9 9
> 10 10 10
>
>
>> do.call(subset, list(dat, subsetexp))
> x y
> 6 6 6
> 7 7 7
> 8 8 8
> 9 9 9
> 10 10 10
>
>> version
> _
> platform i386-pc-mingw32
> arch i386
> os mingw32
> system i386, mingw32
> status
> major 2
> minor 9.1
> year 2009
> month 06
> day 26
> svn rev 48839
> language R
> version.string R version 2.9.1 (2009-06-26)
>
>
> Thank you,
> Vadim
>
>
>
> -----Original Message-----
> From: Charles C. Berry [mailto:cberry at tajo.ucsd.edu]
> Sent: Friday, June 25, 2010 9:16 PM
> To: Vadim Ogranovich
> Cc: 'r-help at r-project.org'
> Subject: Re: [R] converting result of substitute to 'ordidnary' expression
>
> On Fri, 25 Jun 2010, Vadim Ogranovich wrote:
>
>> Dear R users,
>>
>>
>> As substitute() help page points out:
>> Substituting and quoting often causes confusion when the argument
>> is 'expression(...)'. The result is a call to the 'expression'
>> constructor function and needs to be evaluated with 'eval' to give
>> the actual expression object.
>>
>> And indeed I am confused. Consider:
>>
>>> dat <- data.frame(x=1:10, y=1:10)
>>
>>> subsetexp <- substitute(a<x, list(a=5))
>>
>> ## this doesn't work
>>> subset(dat, subsetexp)
>> Error in subset.data.frame(dat, subsetexp) :
>> 'subset' must evaluate to logical
>>
>> ## this does work (thanks to the help page), but one needs to remember to
>> call eval
>>> subset(dat, eval(subsetexp))
>>
>>
>> Is there a way to create subsetexp that needs no eval inside the call to
>> subset()?
>
> I do not think so. See
>
> page(subset.data.frame,'print')
>
> Then think about this:
>
>> eval(substitute(subsetexp))
> 5 < x
>> eval(substitute(subsetexp),list(x=2))
> 5 < x
>> eval(substitute(eval(subsetexp)),list(x=2))
> [1] FALSE
>>
>
> The added layer of substitution is making things a bit tricky.
>
> One alternative is to build up your own call like this:
>
>> sss <- expression(subset(dat,sbst))
>> sss[[1]][[3]] <- subsetexp
>> sss
> expression(subset(dat, 5 < x))
>> eval(sss)
> x y
> 6 6 6
> 7 7 7
> 8 8 8
> 9 9 9
> 10 10 10
>>
>
> HTH,
>
> Chuck
>
>
>>
>> I experimented with the following, but it didn't work:
>>> subsetexp <- eval(substitute(a<x, list(a=5)))
>> Error in eval(expr, envir, enclos) : object 'x' not found
>>
>> Thank you very much for your help,
>> Vadim
>>
>> Note: This email is for the confidential use of the named addressee(s)
>> only and may contain proprietary, confidential or privileged information.
>> If you are not the intended recipient, you are hereby notified that any
>> review, dissemination or copying of this email is strictly prohibited,
>> and to please notify the sender immediately and destroy this email and
>> any attachments. Email transmission cannot be guaranteed to be secure or
>> error-free. Jump Trading, therefore, does not make any guarantees as to
>> the completeness or accuracy of this email or any attachments. This
>> email is for informational purposes only and does not constitute a
>> recommendation, offer, request or solicitation of any kind to buy, sell,
>> subscribe, redeem or perform any type of transaction of a financial
>> product.
>>
>> ______________________________________________
>> 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.
>>
>
> Charles C. Berry (858) 534-2098
> Dept of Family/Preventive
> Medicine
> E mailto:cberry at tajo.ucsd.edu UC San Diego
> http://famprevmed.ucsd.edu/faculty/cberry/ La Jolla, San Diego 92093-0901
>
>
>
> Note: This email is for the confidential use of the named addressee(s)
> only and may contain proprietary, confidential or privileged information.
> If you are not the intended recipient, you are hereby notified that any
> review, dissemination or copying of this email is strictly prohibited, and
> to please notify the sender immediately and destroy this email and any
> attachments. Email transmission cannot be guaranteed to be secure or
> error-free. Jump Trading, therefore, does not make any guarantees as to
> the completeness or accuracy of this email or any attachments. This email
> is for informational purposes only and does not constitute a
> recommendation, offer, request or solicitation of any kind to buy, sell,
> subscribe, redeem or perform any type of transaction of a financial
> product.
>
More information about the R-devel
mailing list