[Rd] Changing function arguments

McGehee, Robert Robert.McGehee at geodecapital.com
Mon Oct 23 18:06:06 CEST 2006


Thanks all. Combining your suggestions, and marking up Gabor's example,
below is the function 'chgArg', which recursively goes through an
expression or language object looking for all functions that contain
'arg', and then incrementing that argument by 'offset'. 

The biggest improvement over the suggestions is that chgArg checks the
formals of the function such that if the user does not supply the
argument, but instead relies on the default, the function will still
increment. Also, 'match.call' is used to match the user's expression
with the function call in case one is relying on positional or partial
matching.

ex:
> FUN <- function(xx = 0, yy = 0, zz = 0) xx + yy + zz
> e <- substitute(FUN() + FUN(x = 5)/FUN(xx = 5) + FUN(1, 2, 3))
> chgArg(e, "xx", 1)
[1] FUN(xx = 1) + FUN(xx = 6)/FUN(xx = 6) + FUN(xx = 2, yy = 2, zz = 3)

The only surprise I came across was when I tried explicitly setting
name/value arguments for a call, the name did not "stick", as it would
with a list (though a call object is _clearly_ not a list).

> e <- substitute(FUN(2))
> e[["xx"]] <- 3
> names(e)
[1] NULL

Meaning, I had to explicitly build the call using 'call()'.

Thanks as always for the help,
Robert

chgArg <- function (e, arg, offset) {
    if (is.expression(e)) return(as.expression(Recall(e[[1]], arg = arg,
offset = offset)))
    if (is.symbol(e) || is.double(e)) return (e)
    if (is.function(get(as.character(e[[1]]))) &&
               arg %in% names(formals(as.character(e[[1]])))) {
        mc <- match.call(get(as.character(e[[1]])), e)
        curArg <- ifelse(is.null(mc[[arg]]),
formals(as.character(e[[1]]))[[arg]], mc[[arg]])
        allArgs <- as.list(mc[-1])
        allArgs[[arg]] <- curArg + offset
        e <- do.call("call", c(as.character(mc[[1]]), allArgs))
    }
    for (i in 1:length(e)) e[[i]] <- Recall(e[[i]], arg = arg, offset =
offset)
    return(e)
}

-----Original Message-----
From: Thomas Lumley [mailto:tlumley at u.washington.edu] 
Sent: Monday, October 23, 2006 10:54 AM
To: McGehee, Robert
Cc: R Development Mailing List
Subject: Re: [Rd] Changing function arguments

On Sun, 22 Oct 2006, McGehee, Robert wrote:

> R-Developers,
> I'm looking for some help computing on the R language.
>
> I'm hoping to write a function that parses a language or expression
> object and returns another expression with all instances of certain
> argument of a given function altered. For instance, say I would like
my
> function, myFun to take an expression and whenever the argument 'x'
> appears within the function FUN inside that expression, return an
> altered expression in which 'x' is incremented by one.
>

This sort of recursive parsing and modification is done by the bquote() 
function, so you could look there.

     -thomas

Thomas Lumley			Assoc. Professor, Biostatistics
tlumley at u.washington.edu	University of Washington, Seattle




More information about the R-devel mailing list