R-beta: S Compatibility (again)

Peter Dalgaard BSA p.dalgaard at biostat.ku.dk
Mon Apr 13 16:55:36 CEST 1998


Peter Dalgaard BSA <p.dalgaard at biostat.ku.dk> writes:

> > Here is a cute example of what can be done in S but not in R.
> > Make a function for the pdf of an order statistic.
> > 
> > > pdf.order <- function(n, r, pfun, dfun) {
> >   con <- round(exp(lgamma(n + 1) - lgamma(r) - lgamma(n - r + 1)))
> >   substitute(
> >     function(x) {
> >       Fx <- p(x)
> >       K*Fx^r1*(1 - Fx)^nr*f(x)
> >     }, 
> >     list(p = substitute(pfun), f = substitute(dfun), 
> >          r1 = r-1, nr = n-r, K = con)
> >   )
> > }
> > > pdf.order(9, 5, pnorm, dnorm)
> > function(x)
> > {
> >         Fx <- pnorm(x)
> >         630 * Fx^4 * (1 - Fx)^4 * dnorm(x)
> > }
> > 
> > The substitute()s to get unevaluated arguments do work but the
> > one to modify the function definitely does not.  substitute() is
> > a very different kind of function in R from what it is in S.
> 
> I see the problem. I suspect that there's a workaround, though. Will
> look at it. 

[a couple of hours later...]

> pdf.order                    
function (n, r, pfun, dfun) 
{
        con <- round(exp(lgamma(n + 1) - lgamma(r) - lgamma(n - 
                r + 1)))
        eval(eval(expression(substitute(function(x) {
                Fx <- p(x)
                K * Fx^r1 * (1 - Fx)^nr * f(x)
        })), list(p = substitute(pfun), f = substitute(dfun), 
                r1 = r - 1, nr = n - r, K = con)), .GlobalEnv)
}
> pdf.order(9, 5, pnorm, dnorm)
function (x) 
{
        Fx <- pnorm(x)
        630 * Fx^4 * (1 - Fx)^4 * dnorm(x)
}
> pdf.order(9, 5, pnorm, dnorm)(0)
[1] 0.981772

This could have been much easier if substitute allowed a named list
like eval() does. I see no reason why it shouldn't...

The necessity of the outer eval is more fundamental: R is sometimes
more stringent in distinguishing between objects and expressions that
evaluate to them. So without this necessary eval (<hehe..>) you'd get
an expression (or more precisely, a "call" object) that evaluates to a
function, not the function itself:

I.e.

S:
> mode(substitute(function()a+b))
[1] "function"

R:
> mode(substitute(function()a+b))
[1] "call"
> mode(eval(substitute(function()a+b)))
[1] "function"

You also need to eval() it in .GlobalEnv {or sys.frame(sys.parent(2))}
, otherwise the result will carry with it the environment of
pdf.order, which is a direct consequence of R's scoping rules.

-- 
   O__  ---- Peter Dalgaard             Blegdamsvej 3  
  c/ /'_ --- Dept. of Biostatistics     2200 Cph. N   
 (*) \(*) -- University of Copenhagen   Denmark      Ph: (+45) 35327918
~~~~~~~~~~ - (p.dalgaard at biostat.ku.dk)             FAX: (+45) 35327907

-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._



More information about the R-help mailing list