[R] matching last argument in function

Alistair Gee alistair.gee at gmail.com
Tue Feb 12 21:10:17 CET 2008


I couldn't get that to work, b/c I need the expr block to be evaluated
after the call to options(). I suspect that list(...) evaluates its
arguments. Here's what I did to your example:

test2 <- function(...) {
   dots <- list(...)    # <======= I think expr is evaluated here.
   if(sum(dots.missing.name <- names(dots) %in% "") > 1)
     stop("Only one argument should have missing name.")
   expr.ind <- ifelse(any(names(dots) == "expr"),
                      which(names(dots) == "expr"),
                      which(dots.missing.name))
   expr <- dots[[expr.ind]]
   opts <- dots[-expr.ind]
   o <- do.call(options, as.list(opts))
   tryCatch(expr, finally=options(o)) # <==== But I want expr evaluated here.
}

a <- seq(1000000, 1000000+15)

test2(width=200, print(a))


I'd like to have expr be unnamed, only b/c I tend to use functions
such as with.options() as flow-control constructs, and not requiring
the last argument to be named is just stylistically nicer, especially
when I nest several flow-control functions like with.options().

Of course, I can always use

  with.options(width=160, scipen=2, expr={
    some_code
  })

or

  with.options(list(width=160, scipen=2), {
    some_code
  })

But I prefer

  with.options(width=160, scipen=2, {
    some_code
  })

So, I'm hoping that this is indeed possible.

On Feb 12, 2008 11:34 AM, Erik Iverson <iverson at biostat.wisc.edu> wrote:
> Yes that will work, that's exactly what I was getting at in my second
> paragraph.  I wrote a function that uses this idea, except the (single)
> unnamed argument can occur anywhere in the function (not necessarily
> last). It will stop if there is more than one unnamed argument.
>
> test2 <- function(...) {
>    dots <- list(...)
>
>    if(sum(dots.missing.name <- names(dots) %in% "") > 1)
>      stop("Only one argument should have missing name.")
>
>    expr.ind <- ifelse(any(names(dots) == "expr"),
>                       which(names(dots) == "expr"),
>                       which(dots.missing.name))
>
>    expr <- dots[[expr.ind]]
>    opts <- dots[-expr.ind]
>    opts
> }
>
>
>
> Gabor Csardi wrote:
> > It should be possible i think. You just supply all the arguments via
> > '...' and then cut off the last one. I don't see why this wouldn't work,
> > but maybe i'm missing something.
> >
> > Gabor
> >
> > On Tue, Feb 12, 2008 at 12:58:25PM -0600, Erik Iverson wrote:
> >> Alistair -
> >>
> >> I don't believe this is possible.  The only way formal arguments (like
> >> expr) can be matched after a '...' is with *exact* name matching.  Why
> >> do you want to avoid explicitly naming the expr argument?
> >>
> >> If you always want the expr argument last, you might be able to just use
> >> ... as the sole argument to your function, and strip off the last
> >> element inside the function as 'expr', and use all but the last element
> >> as your list of options.  This requires that expr always be given last
> >> though.  Probably best just to explicitly name the expr argument.
> >>
> >> Erik Iverson
> >>
> >> Alistair Gee wrote:
> >>> I often want to temporarily modify the options() options, e.g.
> >>>
> >>> a <- seq(10000001, 10000001 + 10) # some wide object
> >>>
> >>> with.options <- function(..., expr) {
> >>>   options0 <- options(...)
> >>>   tryCatch(expr, finally=options(options0))
> >>> }
> >>>
> >>> Then I can use:
> >>>
> >>> with.options(width=160, expr = print(a))
> >>>
> >>> But I'd like to avoid explicitly naming the expr argument, as in:
> >>>
> >>> with.options(width=160, print(a))
> >>>
> >>> How can I do this with R's argument matching? (I prefer the expr as
> >>> the last argument since it could be a long code block. Also, I'd like
> >>> with.options to take multiple options.)
> >>>
> >>> TIA
> >>>
> >>> ______________________________________________
> >>> 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.
> >> ______________________________________________
> >> 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