[Rd] Test for argument in ...
Gabor Grothendieck
ggrothendieck at gmail.com
Sun Jul 2 05:19:21 CEST 2006
That's because you are passing the argument twice. Try this:
> foo1 <- function(x, ...)
+ {
+ L <- list(...)
+ if (is.null(L$decreasing)) L$decreasing <- TRUE
+ do.call(order, c(list(x), L))
+ }
>
> foo1(c(5, 2, 3, 4), decreasing=FALSE)
[1] 2 3 4 1
On 7/1/06, Gregor Gorjanc <gregor.gorjanc at gmail.com> wrote:
> Hi,
>
> Gabor Grothendieck wrote:
> > Try this:
> >
> >> f <- function(...) if (!is.null(list(...)$arg1)) cat("arg1 found\n")
> >> else cat("arg1 not found\n")
> >> f(arg1 = 3)
> > arg1 found
> >> f(arg2 = 3)
> > arg1 not found
>
> Actually it is not OK. Bellow is simplified example that shows, what I
> would like to do:
>
> foo1 <- function(x, ...)
> {
> if(is.null(list(...)$decreasing)) {
> decreasing <- TRUE
> } else {
> decreasing <- list(...)$decreasing
> }
> return(order(x, ..., decreasing=decreasing))
> }
>
> > foo1(c(5, 2, 3, 4))
> [1] 1 4 3 2
>
> >foo1(c(5, 2, 3, 4), decreasing=FALSE)
> Error in order(x, ..., decreasing = decreasing) :
> formal argument "decreasing" matched by multiple actual arguments
>
> > On 7/1/06, Gregor Gorjanc <gregor.gorjanc at gmail.com> wrote:
> >> Hello!
> >>
> >> Say I have a function foo1, which has argument ... to pass various
> >> arguments to foo2 i.e.
> >>
> >> foo1 <- function(x, ...)
> >> {
> >> foo2(x, ...)
> >> }
> >>
> >> Say that foo2 accepts argument arg1 and I would like to do the following:
> >> - if foo1 is called as foo1(x) then I would like to assign some value to
> >> arg1 inside foo1 before calling foo2
> >>
> >> arg1 <- "some value"
> >> foo2(x, arg1=arg1)
> >>
> >> - if foo1 is called foo1(arg1="some other value") do not assign some
> >> value to arg1 and call foo2
> >>
> >> foo2(arg1=arg1)
> >>
> >> However, I am not able to do this since I do not know how to test/check
> >> if arg1 was given in foo1. Is it possible to test whether some argument
> >> was passed in "..." i.e. something like
> >>
> >> foo1 <- function(x, ...)
> >> {
> >> if(testForArgumentInThreeDots(arg1)) arg1 <- "some value"
> >> foo2(x, arg1=arg1, ...)
> >> }
> >>
> >> Thanks!
> >>
> >> --
> >> Lep pozdrav / With regards,
> >> Gregor Gorjanc
> >>
> >> ----------------------------------------------------------------------
> >> University of Ljubljana PhD student
> >> Biotechnical Faculty
> >> Zootechnical Department URI: http://www.bfro.uni-lj.si/MR/ggorjan
> >> Groblje 3 mail: gregor.gorjanc <at> bfro.uni-lj.si
> >>
> >> SI-1230 Domzale tel: +386 (0)1 72 17 861
> >> Slovenia, Europe fax: +386 (0)1 72 17 888
> >>
> >> ----------------------------------------------------------------------
> >> "One must learn by doing the thing; for though you think you know it,
> >> you have no certainty until you try." Sophocles ~ 450 B.C.
> >>
> >> ______________________________________________
> >> R-devel at r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>
>
>
> --
> Lep pozdrav / With regards,
> Gregor Gorjanc
>
> ----------------------------------------------------------------------
> University of Ljubljana PhD student
> Biotechnical Faculty
> Zootechnical Department URI: http://www.bfro.uni-lj.si/MR/ggorjan
> Groblje 3 mail: gregor.gorjanc <at> bfro.uni-lj.si
>
> SI-1230 Domzale tel: +386 (0)1 72 17 861
> Slovenia, Europe fax: +386 (0)1 72 17 888
>
> ----------------------------------------------------------------------
> "One must learn by doing the thing; for though you think you know it,
> you have no certainty until you try." Sophocles ~ 450 B.C.
> ----------------------------------------------------------------------
>
>
More information about the R-devel
mailing list