[R] Additional arguments in S3 method produces a warning

Martin Maechler maechler at stat.math.ethz.ch
Thu Mar 16 08:52:36 CET 2006


>>>>> "HenrikB" == Henrik Bengtsson <hb at maths.lth.se>
>>>>>     on Thu, 16 Mar 2006 07:48:49 +0100 writes:

    HenrikB> It is even better/more generic(!) to have: 
    HenrikB> extract <- function(...) UseMethod("extract")

    HenrikB> "Specifying the object argument or the method
    HenrikB> arguments of a generic function will restrict any
    HenrikB> other methods with the same name to have the same
    HenrikB> argument. By also excluding the object argument,
    HenrikB> default functions such as search() will also be
    HenrikB> called if the generic function is called without
    HenrikB> any arguments."
    HenrikB> [http://www.maths.lth.se/help/R/RCC/]

    HenrikB> /Henrik

Hmm, sorry, but that is Henrik's own ``style sheet'' which
contains some views that I (and AFAIK other R-core members) 
do not share.

The grain of truth in Henrik's statement is that for a generic
function, S3 or S4, one should carefully consider which
arguments should be shared by all methods and which not.
But having at least one  `` non-... '' argument should be the
rule, and is even a necessity for S4.
Hence I'd strongly discourage defining generic functions with
only a (...) argument list.

    HenrikB> On 3/15/06, Gabor Grothendieck
    HenrikB> <ggrothendieck at gmail.com> wrote:
    >> Define extract like this:
    >> 
    >> extract <- function(e, n, ...) UseMethod("extract")
    >> 
    >> # test -- no warning 
    >> extract(tp, no.tp = FALSE, peak = TRUE, pit = FALSE)

yes, I agree with Gabor

Martin Maechler,
ETH Zurich

> On 3/15/06, Philippe Grosjean <phgrosjean at sciviews.org> wrote:
> > Hello,
> > I just notice this:
> >  > x <- c(1:4,0:5, 4, 11)
> >  > library(pastecs)
> > Loading required package: boot
> >  > tp <- turnpoints(x)
> >  > extract(tp, no.tp = FALSE, peak = TRUE, pit = FALSE)
> >  [1] FALSE FALSE FALSE  TRUE FALSE FALSE FALSE FALSE FALSE  TRUE FALSE
> > FALSE
> > Warning message:
> > arguments after the first two are ignored in: UseMethod("extract", e, n,
> > ...)
> >  > extract(tp)
> >  [1]  0  0  0  1 -1  0  0  0  0  1 -1  0
> > Warning message:
> > arguments after the first two are ignored in: UseMethod("extract", e, n,
> > ...)
> >
> > My extract.turnpoints() function produces warnings. I can easily spot
> > the origin of this warning:
> >
> >  > extract
> > function (e, n, ...)
> > UseMethod("extract", e, n, ...)
> >  > extract.turnpoints
> > function (e, n, no.tp = 0, peak = 1, pit = -1, ...)
> > {
> >     if (missing(n))
> >         n <- length(e)
> >     res <- rep(no.tp, length.out = e$n)
> >     res[e$pos[e$peaks]] <- peak
> >     res[e$pos[e$pits]] <- pit
> >     if (n < length(res) & n > 0)
> >         res <- res[1:n]
> >     res
> > }
> >
> > This is because my extract.turnpoints() method defines more arguments
> > than 'e' and 'n' in the generic function. However,
> >
> > 1) I though that the '...' argument in S3 generic function was there to
> > allow defining/passing additional arguments in/to S3 methods. Is this
> > correct? If yes, why the warning?
> >
> > 2) Despite the warning says arguments after the first two are ignored,
> > this appears not to be the case: in this example, 'no.tp', 'peak' and
> > 'pit' arguments are taken into account, as you can see (different
> > behaviour if you give other values to them).
> >
> > I am a little bit lost. Could someone help me, please.
> >
> > Best,
> >
> > Philippe Grosjean
> >




More information about the R-help mailing list