[Rd] Use of all/any

Bill Dunlap bill at insightful.com
Fri Oct 26 21:46:25 CEST 2007


On Fri, 26 Oct 2007, Martin Maechler wrote:

> Apropos Bill Dunlap's note:  Do newer versions of S-plus warn?
> At least up to 6.2.2, I'm pretty sure no S version has warned
> about
> 	X <- c(0.1, pi)
> 	all(X) > 0.5

Hi Martin,

No, it doesn't warn.  We had a user who ran into a bug
in another function that came from this sort of thing
so I wrote some code that examined parse trees for
expresions of the form
    <comparison operator>
        <call to any or all>
        <anything>
or
    <comparison operator>
        <anything>
        <call to any or all>
and ran it over all our source code.  Out of curiousity
I also ran it over the current R source and an out-of-date
copy of the package source code from CRAN and that is
where I ran across the problem in polr() (and lots of instances
in packages, although they seemed to be clustered).

Now I have a question/complaint about doing this.  In Splus
I looked for this pattern with the following code
   isComparisonOfAnyOrAll <- function(expr)
      isCallTo(expr, c("<", ">", "<=", ">=", "==")) &&
        (isCallTo(expr[[2]], c("any", "all")) ||
         isCallTo(expr[[3]], c("any", "all")))
where isCallTo is
   isCallTo <- function(expr, functionName, numberArgs = NULL)
   {
        # return TRUE if expr is a call to with one of the functions
	# listed in functionName.  If numberArgs is non-NULL, it should
	# be a nonnegative integer giving the required number of arguments
	# in the call
        if(class(expr) == "call with ...") {
                # e.g., Quote(foo(x, ..., value = TRUE))
                # This class is only in Splus
                if(!is.null(numberArgs)) {
                        warning("call has ... in argument list, numberArgs will count all ... arguments as 1 argument"
                                )
                }
                expr <- expr[[1]]
        }
        if(length(functionName) == 1) {
                retval <- class(expr) == "call" && identical(expr[[1]], as.name(
                        functionName)) && (is.null(numberArgs) || numberArgs ==
                        length(expr) - 1)
        }
        else {
                retval <- class(expr) == "call" && is.name(expr[[1]]) &&
                        is.element(as.character(expr[[1]]), functionName) &&
                        (is.null(numberArgs) || numberArgs == length(expr) -
                        1)
        }
        retval
   }
This code works in Splus and R.  E.g.,
   > isComparisonOfAnyOrAll(Quote(any(x)<0))
   [1] TRUE
   > isComparisonOfAnyOrAll(Quote(any(x<0)))
   [1] FALSE

In Splus I use
   rapply(expr, classes="call",
     f=function(x)if(isComparisonOfAnyOrAll(x))deparseText(x))
to rattle down an an expression tree looking for this pattern.
However's R's rapply won't let me do that because
it insists its input be a function instead of being of
recursive type.  Its help file says it evaluates the arguments
to f() even if they are expressions, and that may contribute
to problems.  The Splus rapply accepts any recursive type and it does not
evaluate the subtrees that it hands to f().

E.g., running the same input into R and Splus and labelling
the output lines 'Splus:' and 'R   :', we get
  RS> rapply(function(x)log(x+1), f = function(expr) if (is.name(expr)) as.character(expr)) # all.names()
  Splus: [1] "log" "+"   "x"
  R    : Error in rapply(function(x) log(x + 1), f = function(expr) if (is.name(expr)) as.character(expr)) :
  R    :  'object' must be a list
If I get around the "'object' must be a list' problem by wrapping
the input in a list then I run into the evalution problem

Does R have an rapply-like function that works like Splus's?

Are the R parse tree classes sufficiently different from lists
that we cannot expect the above to work?

In Splus I've used rapply quite productively to find patterns
in parse trees and then change the code.  E.g., to change all
calls of the form
    log(x, base)
to
    logb(x, base)
but not change calls of the form log(x) you can do
    > changeLogCalls<-function(func) {
        rapply(func, classes="call", how="replace",
            function(expr){
                if(isCallTo(expr,"log",2)) expr[[1]] <- as.name("logb")
                expr
            })
    }
    }
    > changeLogCalls(function(x)log(x,2)/log(x))
    function(x)
    logb(x, 2)/log(x)

I suspect I should be looking in codetools for this sort of
thing.

----------------------------------------------------------------------------
Bill Dunlap
Insightful Corporation
bill at insightful dot com

 "All statements in this message represent the opinions of the author and do
 not necessarily reflect Insightful Corporation policy or position."



More information about the R-devel mailing list