[Rd] Do *not* pass '...' to NextMethod() - it'll do it for you; missing documentation, a bug or just me?

Henrik Bengtsson hb at biostat.ucsf.edu
Wed Oct 17 07:48:10 CEST 2012


Hi Simon,

thanks for the prompt reply.  Comments below...

On Tue, Oct 16, 2012 at 7:35 PM, Simon Urbanek
<simon.urbanek at r-project.org> wrote:
>
> On Oct 16, 2012, at 9:53 PM, Henrik Bengtsson wrote:
>
>> Hi,
>>
>> although I've done S3 dispatching for more than a decade now, I think
>> I managed to overlook/avoid the following pitfall when using
>> NextMethod():
>>
>> If you explicitly pass argument '...' to NextMethod(), you will
>> effectively pass those argument twice to the "next" method!
>>
>>
>> EXAMPLE:
>>
>> foo0 <- function(...) UseMethod("foo0");
>> foo1 <- function(...) UseMethod("foo1");
>> foo2 <- function(...) UseMethod("foo2");
>>
>> foo2.A <- foo1.A <- foo0.A <- function(object, a=1, b=2, c=3, d=4, ...) {
>>  str(c(list(object=object, a=a, b=b, c=c, d=d), list(...)));
>> }
>>
>> ## CORRECT: Don't pass arguments '...', but all other
>> ## *named* arguments that you wish to be changed in the call.
>> foo0.B <- function(object, ..., b=-2) {
>>  NextMethod("foo0", object=object, b=b);
>> }
>>
>> ## INCORRECT: Passing arguments '...' explicitly will *duplicated* them.
>> foo1.B <- function(object, ..., b=-2) {
>>  NextMethod("foo1", object=object, ..., b=b);
>> }
>>
>> ## INCORRECT: As an illustration, *triplication* of arguments '...'.
>> foo2.B <- function(object, ..., b=-2) {
>>  NextMethod("foo2", object=object, ..., ..., b=b);
>> }
>>
>> objB <- structure(NA, class=c("B", "A"));
>>
>> foo0(objB, "???", "!!!");
>> ## Gives:
>> ## List of 5
>> ##  $ object:Classes 'B', 'A'  logi NA
>> ##  $ a     : chr "???"
>> ##  $ b     : num -2
>> ##  $ c     : chr "!!!"
>> ##  $ d     : num 4
>>
>> foo1(objB, "???", "!!!");
>> ## Gives:
>> ## List of 6
>> ##  $ object:Classes 'B', 'A'  logi NA
>> ##  $ a     : chr "???"
>> ##  $ b     : num -2
>> ##  $ c     : chr "!!!"
>> ##  $ d     : chr "???"
>> ##  $       : chr "!!!"
>>
>> foo2(objB, "???", "!!!");
>> ## Gives:
>> ## List of 8
>> ##  $ object:Classes 'B', 'A'  logi NA
>> ##  $ a     : chr "???"
>> ##  $ b     : num -2
>> ##  $ c     : chr "!!!"
>> ##  $ d     : chr "???"
>> ##  $       : chr "!!!"
>> ##  $       : chr "???"
>> ##  $       : chr "!!!"

Just to give further practical motivation for the latter case:

foo1.C <- function(object, ..., c=-3) {
  NextMethod("foo1", object=object, ..., c=c);
}

objC <- structure(NA, class=c("C", "B", "A"));

foo1(objC, "???", "!!!")
## List of 11
##  $ object:Classes 'C', 'B', 'A'  logi NA
##  $ a     : chr "???"
##  $ b     : num -2
##  $ c     : num -3
##  $ d     : chr "!!!"
##  $       : chr "???"
##  $       : chr "!!!"
##  $       : chr "???"
##  $       : chr "!!!"
##  $       : chr "???"
##  $       : chr "!!!"

>>
>> This behavior does not seem to be documented (at least not
>> explicitly),
>
> I would argue it does:
> "Normally ‘NextMethod’ is used with only one argument, ‘generic’, but if further arguments are supplied these modify the call to the next method."
> The whole point of NextMethod is that it starts off with the full call *including* ... from the function - by calling NextMethod you are modifying that call, so by adding unnamed arguments you will append them.

Maybe it's possible to make help("NextMethod") more explicit about
this?  It's a bit tricky because there are two different '...'; one for
NextMethod() and one for the S3 function that calls NextMethod().
What about:

\item{...}{\emph{further} arguments to be passed to the next method.
Named arguments will override same-name arguments to the function
containing NextMethod, otherwise they will be appended.  Non-named
arguments (including those passed as \code{...}) will be appended.}

instead of as now:

\item{...}{further arguments to be passed to the next method.},

and adding the following note to the Details section of help("NextMethod"):

NextMethod invokes the next method (determined by the class vector,
either of the object supplied to the generic, or of the first argument
to the function containing NextMethod if a method was invoked
directly). Normally NextMethod is used with only one argument,
generic, but if further arguments are supplied these _modify_ the call
to the next method.  Note, if the function containing NextMethod has
an argument '...', it is likely a mistake to pass it explicitly to
NextMethod, because such will be \emph{appended} to the set of
arguments passed to this function (already containing '...') and
therefore result in duplicated entries.

>
> And the ... override is explicitly documented: "Any named arguments matched to ‘...’ are handled specially: they either replace existing arguments of the same name or are appended to the argument list." Try foo1(objB, c="foo", "bla") in your example - it illustrates the difference.

Yes, that part I understood, but thanks for the clarification.

>
> Also why would you pass ... when you don't do it for UseMethod?

Yes, I tried to make that analogue as well, but however I looked at
'...' and UseMethod()/NextMethod() I saw multiple interpretations.
Maybe less so now after spending hours of testing/reading the source
code (and trying to find a better documentation/alternative algorithm
for NextMethod()/understanding the developer's intentions).  From a
more practical point of view, (since R v1.8.0 or so) UseMethod() gives
an error if you pass it more than two arguments, which in turn begs
the question if NextMethod() could give an error is you pass an
explicit '...' (unless one can argue that there are use cases when
that is wanted).

Looking at my own packages, I found several occurrences where I pass
'...' to NextMethod().  I'd bet you I'm not the only one that has
been/will be bitten by this behavior.  Indeed, in R devel (r60951)
there are a few cases:

% cd src/library/
% grep 'NextMethod("[^)]*[.][.][.])' */R/*.R
(The above grep will not catch cases where NextMethod() spans multiple
lines.  However, I could only find one such case and it did not pass
'...').

base/R/print.R:##- Need '...' such that it can be called as
NextMethod("print", ...):
stats/R/ts.R:    NextMethod("print", x, quote = FALSE, right = TRUE, ...)
utils/R/citation.R:    NextMethod("print", x, style = style, ...)
utils/R/str.R:  invisible(NextMethod("str", ...))
utils/R/str.R:    else invisible(NextMethod("str", give.length=FALSE,...))

none of which look serious, but explains for instance why you get:

> x <- ts(1:10, frequency=4, start=c(1959, 2))
> class(x)
[1] "ts"
> print(x, calendar=TRUE, 3L)
Error in print.default(x, calendar = TRUE, 3L, quote = FALSE, right = TRUE) :
  invalid 'na.print' specification

Try debug(print.default) and you'll see that both 'digits' and
'na.print' are assigned 3L (despite what the call in the debug output
says).  Instead, you have to do:

> print(x, calendar=TRUE, digits=3L)
     Qtr1 Qtr2 Qtr3 Qtr4
1959         1    2    3
1960    4    5    6    7
1961    8    9   10

Maybe 'R CMD check' should give a NOTE, WARNING, or ERROR on passing
'...' to NextMethod()?

Thanks,

Henrik

>
> Cheers,
> Simon
>
>
>
>> cf. help("NextMethod", package="base") and Section
>> 'NextMethod' in 'R Language Definition'.  I don't have the 'White
>> Book', so I don't know what that is saying about this.
>>
>> I can reproduce this on Windows, OSX and Linux and various versions of
>> R, e.g. R v2.10.0, R v2.15.1 patched, R devel.
>>
>> Is this a bug, should it be detected as a user error, should it be
>> documented, or is this already old news?
>>
>> Thanks,
>>
>> Henrik
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>>
>



More information about the R-devel mailing list