Duncan Murdoch wrote:
> Okay, here's my effort based on Deepayan's and Charles' ideas. The
> newArgs function is not what I'd call transparent, but I like the way
> the wrapper looks.
>
> > newArgs <- function(..., Params) {
> + f <- function(...) list(...)
> + formals(f) <- c(Params, form
Whoops, just noticed that I cut when I should have copied. The newArgs
function should look like this:
newArgs <- function(..., Params) {
f <- function(...) list(...)
formals(f) <- c(Params, formals(f))
names <- as.list(names(Params))
names(names) <- names
names <- lapply(names, a
Okay, here's my effort based on Deepayan's and Charles' ideas. The
newArgs function is not what I'd call transparent, but I like the way
the wrapper looks.
> newArgs <- function(..., Params) {
+ f <- function(...) list(...)
+ formals(f) <- c(Params, formals(f))
+ b <- as.list(body(f))
+
On 3/7/2006 2:00 PM, Deepayan Sarkar wrote:
>
> On 3/7/06, Duncan Murdoch <[EMAIL PROTECTED]> wrote:
>> I'm writing wrappers for some functions that change some of the default
>> arguments. I'd rather not list all of the arguments for the low level
>> functions because there are about a dozen w
On 3/7/06, Duncan Murdoch <[EMAIL PROTECTED]> wrote:
> I'm writing wrappers for some functions that change some of the default
> arguments. I'd rather not list all of the arguments for the low level
> functions because there are about a dozen wrapper functions, and about
> 20 arguments to low
On 3/7/2006 12:08 PM, Charles Dupont wrote:
> Duncan Murdoch wrote:
>> I'm writing wrappers for some functions that change some of the default
>> arguments. I'd rather not list all of the arguments for the low level
>> functions because there are about a dozen wrapper functions, and about
>> 20
Here's a slightly different approach:
lowlevel <- function(longname = 1, ...) {
cat("longname = ", longname, "\n")
}
wrapper <- function(...) {
newargs <- defaults(list(...), list(longname = 2))
do.call("lowlevel", newargs)
}
defaults <- function(x, defaults) {
if (length(x) == 0)
Duncan Murdoch wrote:
> I'm writing wrappers for some functions that change some of the default
> arguments. I'd rather not list all of the arguments for the low level
> functions because there are about a dozen wrapper functions, and about
> 20 arguments to lowlevel. Instead I'm trying someth
The original code was not intended to be fully finished.
It was just to give the idea so I left out the error checking.
Adding such a check is just a matter of adding an if
statement to check the pmatch for NA:
wrapper <- function(...) {
args <- list(...)
if (length(args)) {
nf <- names(f
On 3/7/2006 9:42 AM, Gabor Grothendieck wrote:
> Try this:
>
>
> wrapper <- function(...) {
> args <- list(...)
> if (length(args)) {
> nf <- names(formals(lowlevel))
> nams <- nf[pmatch(names(args), nf)]
> args <- replace(list(longname = 2), nams, args)
> }
> do.c
Try this:
wrapper <- function(...) {
args <- list(...)
if (length(args)) {
nf <- names(formals(lowlevel))
nams <- nf[pmatch(names(args), nf)]
args <- replace(list(longname = 2), nams, args)
}
do.call("lowlevel", args)
}
Here is a test:
> wrapper()
longname
11 matches
Mail list logo