[R] matching last argument in function

Gabor Grothendieck ggrothendieck at gmail.com
Wed Feb 13 19:35:50 CET 2008


Add envir = parent.frame() to the do.call:


with.options <- function(...) {
    L <- as.list(match.call())[-1]
    len <- length(L)
    old.options <- do.call(options, L[-len], envir = parent.frame())
    on.exit(options(old.options))
    invisible(eval.parent(L[[len]]))
}

# test
with.options(width = 40, print(1:25))
test <- function(w) with.options(width = w, print(1:25))
test(40)


On Feb 13, 2008 1:29 PM, Alistair Gee <alistair.gee at gmail.com> wrote:
> Hi Gabor,
>
> That almost works ... but it fails when I nest with.options() within
> another function:
>
> with.options <- function(...) {
>   L <- as.list(match.call())[-1]
>   len <- length(L)
>   old.options <- do.call(options, L[-len])
>   on.exit(options(old.options))
>   invisible(eval.parent(L[[len]]))
> }
>
> with.width <- function(w)
>  with.options(width=w, print(1:25))
>
> m.with.width(10)
>
> > Error in function (...)  : object "w" not found
>
> Enter a frame number, or 0 to exit
>
> 1: with.width(10)
> 2: with.options(width = w, print(1:25))
> 3: do.call(options, L[-len])
> 4: function (...)
>
> I tried, unsuccessfully, to fix the problem by using eval.parent()
> around do.call() and around L[-len].
>
> This problem does not occur if I use my original implementation:
>
> with.options <- function(..., expr) {
>  options0 <- options(...)
>  tryCatch(expr, finally=options(options0))
> }
>
> I realize that I can use my original implementation in this particular
> case, but I'd like to have a single implementation that works
> correctly, while not requiring explicitly naming the expr argument.
>
> TIA
>
>
> On Feb 12, 2008 12:43 PM, Gabor Grothendieck <ggrothendieck at gmail.com> wrote:
> > Try this:
> >
> > with.options <- function(...) {
> >     L <- as.list(match.call())[-1]
> >     len <- length(L)
> >     old.options <- do.call(options, L[-len])
> >     on.exit(options(old.options))
> >     invisible(eval.parent(L[[len]]))
> > }
> >
> > > with.options(width = 40, print(1:25))
> >  [1]  1  2  3  4  5  6  7  8  9 10 11 12
> > [13] 13 14 15 16 17 18 19 20 21 22 23 24
> > [25] 25
> > > with.options(width = 80, print(1:25))
> >  [1]  1  2  3  4  5  6  7  8  9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25
> >
> >
> >
> >
> >
> > On Feb 12, 2008 12:45 PM, Alistair Gee <alistair.gee at gmail.com> 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.
> > >
> >
>



More information about the R-help mailing list