[R] Extract the names of the arguments in an "expression"
Kenn Konstabel
lebatsnok at gmail.com
Thu Mar 24 13:29:24 CET 2011
I tried this as an exercise and here's what I arrived to:
collector <- function(expr){
RES <- list()
foo <- function(x) unlist(lapply(x, as.list))
EXPR <- foo(expr)
while(length(EXPR) >0){
if(is.symbol(EXPR[[1]])){
RES <- c(RES, EXPR[[1]])
EXPR <- EXPR[-1]
next
}
if(is.atomic(EXPR[[1]])){
EXPR <- EXPR[-1]
next
}
EXPR <- if(length(EXPR)==1) foo(EXPR[[1]]) else
c(foo(EXPR[[1]]), EXPR[-1])
}
sapply(RES, as.character)
}
It worked as expected on all 4 or 5 expressions I tried (you could add
"unique" to the last line) but it may be safer to use what's already
available in the codetools package as Duncan Murdoch suggested.
But of course, * and cos in your example are also returned, as well as
any extra parentheses, so
> collector(expression((1)))
# [1] "("
You can however exclude the functions found in e.g. base package ( see
ls("package:base", all=TRUE) ) but then, a user-defined variable in
your expression may well be called, e.g. "url" or "T", and these are
found int the base package.
Regards,
Kenn
2011/3/24 Javier López-de-Lacalle <javier.lopezdelacalle at ehu.es>:
> Hi everybody:
>
> I need to get the names of the arguments in an object of class "expression".
> I've got the following expression:
>
>> x <- expression(rho * cos(omega))
>
> Is there any function or procedure that returns the names of the arguments
> (in the example: "rho" and "omega")?
>
> I tried a rough approach implemented in the function expr.args() shown
> below. As the function eval() needs to get access to those arguments, a
> possible approach is as follows: 1) apply eval() to the expression "x"
> within an empty environment; 2) get the variable names from the character
> string containing the error message that will be returned:
>
> "Error in eval(expr, envir, enclos) : object 'rho' not found";
>
> 3) assign a value to the first identified variable, "rho", and apply eval()
> again until the expression is evaluated and no error returned.
>
> There are some pitfalls in this approach, expr.args():
>
> i) it is a recursive procedure (I guess there must be a more
> efficient approach);
>
> ii) it does not work if some of the arguments, for instance 'rho',
> exist in the workspace. Despite a new environment is created to evaluate the
> expression, objects are also searched in the parent environment. The search
> should somehow stick to the new environment (called 'tmpe' in expr.args());
>
> iii) it does not work if the name of an argument coincides with the
> name of a function (for instance 'gamma').
>
> Is there any function to do this task? If not, I would appreciate some
> guidance to improve the function expr.args().
>
>> expr.args <- function(x)
> {
> cond <- is.expression(x)
> if (cond) {
> tmpe <- new.env()
> } else return()
>
> while (cond)
> {
> ref <- try(eval(x, envir = tmpe), silent = TRUE)
> if (cond <- (class(ref) == "try-error"))
> {
> if (length(grep("not found", ref[1])) > 0)
> {
> aux <- substr(ref, regexpr("object ", ref) + 8, regexpr(" not
> found", ref) - 2)
> assign(as.character(aux), 1, envir = tmpe)
> } else stop("expression could no be evaluated but a missing variable
> was not identified.")
> }
> }
>
> ls(envir = tmpe)
> }
>
> Many thanks.
>
> javi
>
> ______________________________________________
> 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.
>
More information about the R-help
mailing list