[Rd] UseMethod call with no arguments - solved, I think

Henrik Bengtsson hb at maths.lth.se
Fri Nov 19 20:40:25 CET 2004


> -----Original Message-----
> From: r-devel-bounces at stat.math.ethz.ch 
> [mailto:r-devel-bounces at stat.math.ethz.ch] On Behalf Of Prof 
> Brian Ripley
> Sent: Tuesday, November 16, 2004 1:36 PM
> To: Henrik Bengtsson
> Cc: R-devel at r-project.org
> Subject: RE: [Rd] UseMethod call with no arguments - solved, I think
> 

> > My concern/interpretation was that
> >
> > bar <- function(...) UseMethod("bar")
> >
> > is deprecated (where I saw "..." as the "arguments"). Reading 
> > ?UseMethod
> 
> I don't read that as being supported, and it does not work in 
> S.  `...' is 
> not strictly an argument of a function, and is usually documented as 
> `further arguments'.
> 
> > more carefully (it still says) - "If it is called with just one 
> > argument, the class of the first argument of the enclosing 
> function is 
> > used as
> > 'object': unlike S this is the actual argument passed and 
> not the current
> > value of the object of that name." - I see that the above 
> should still be
> > fine.
> 
> > So, now the note makes perfectly sense and it is *not* a "big step".
> 
> However, removing undocumented features can happen at any 
> time.  There is 
> danger in using unusual constructions that may be allowed 
> according to 
> some particular reading of some of the documentation.  In particular, 
> consider the following
> 
> > bar <- function(..., x) UseMethod("bar")
> > bar.foo <- function(..., x) print("foo")
> > x <- structure(1, class="foo")
> > bar(x) # arg is part of ...
> [1] "foo"
> > bar(x=x) # arg is matched to x
> [1] "foo"
> > bar(1, x=x)
> Error in bar(1, x) : no applicable method for "bar"

...and you wish to dispatch on 'x', which *can* be done with
UseMethod("bar", x")? In S3, where you can only dispatch on *one* object, is
there really a rational for *not* putting the object as a first argument?
Maybe...

For curiosity, I grepped the R v2.0.1 source for occurances where
UseMethod() is called with more than the one argument. Then I search for
those generic function who does not dispatch based on the first argument.
The result is:

% cd src/library/
% grep 'UseMethod(' */R/*.R | wc -l

  232   # nbr of usage of UseMethod

% grep -h -B 2 -E "^[ ]*[^#].*UseMethod[(][ ]*[\"'][^\"']*[\"'][ ]*[,]"
*/R/*.R

widthDetails <- function(x) {
  UseMethod("widthDetails", x)
--

heightDetails <- function(x) {
  UseMethod("heightDetails", x)

Recommended packages:
% for f in Recommended/*.tar.gz; do gunzip -c $f | tar -xO | grep -E "^[
]*[^#].*UseMethod[(][ ]*[\"'][^\"']*[\"'][ ]*[,]"; done

loglm1 <- function(formula, data, ...) UseMethod("loglm1", data)

So, only three generic functions in R distribution call UseMethod() with
more than one argument, and one of these are dispatching on the second
argument, not the first. The others call UseMethod() with one arguments,
maybe for the same reason as I will use below; minimize redundancy => easier
to maintain and less risk for bugs.

Continuing...

CRAN (419 packages):
The script and complete output is attached. 

I found the following packages (bundles were not checked) and generic
functions dispatching on another argument than the first (indeed, all on the
2nd):

Zeilig: sim <- function(object, x, ...) UseMethod("sim", x) 
ipred: bagging <- function(formula, data, ...) UseMethod("bagging", data) 
ipred: errorest <- function(formula, data, ...) UseMethod("errorest", data) 
ipred: inbagg <- function(formula, data, ...) UseMethod("inbagg", data) 
ipred: inclass <- function(formula, data, ...) UseMethod("inclass", data) 
maxstat: maxstat.test <- function(formula, data, ...)
UseMethod("maxstat.test", data)

Indeed, there are a few method dispatching on the 2nd argument. 

Interestingly, almost all of these seem to have a 'formula' as the first
argument and a data object as a second, which they dispatch on. This, was
actually the only case I could think of that would make sense; the 'formula'
object is somewhat more "important" than the 'data' object and is therefore
put first.

Your last call of your next example demonstrates a potential problem for the
above methods;

> > bar <- function(y, x, ...) UseMethod("bar")
> > bar(x) # matches y
> [1] "foo"
> > bar(x=x) # matches x
> [1] "foo"
> 
> and I don't think there is any intention that such behaviour will 
> necessarily continue (the last one does look like an error).  The 
> rules seem not to be written down clearly enough.'

Yes, it definitely looks like an error. 

However, of the above identified generic functions, will they be called
without the first argument? I would say, probably not. However, you can
always argue that the user may swap the order;

> y=1
> bar(x=x, y=y) # matches x

which is a *real* problem I would say. In the real world (the methods with
'formula' found above), that could be a problem, but I do not think it would
be hard to be explicit about this in the documentation/help.

There is of course a reason for why I put time on this, and it is because I
find extremely useful to write my generic function as

 generic <- function(...) UseMethod("generic")

This way I leave it open do *anyone* to use whatever arguments they want in
their 'generic.Class' methods (in case they have one of my package loaded).
Now I learned to add "...as long as they assume dispatching on the first
argument". 

Doing will minimize the risk for naming conflicts between existing packages
(that I do not know of, and of my packages that others do not know of),
between existing and future packages, between existing packages and future
added/modified core functions in R etc. 

Also, if I want to use a generic function called 'foo()', but there already
exists another function (or generic function) in another package (or in R)
identically named, then it is possible to test for this, try to redefine the
existing generic function etc, and replace it with the above construct. 

My (internal) setGenericS3() in R.oo, which is called by setMethodS3(), does
this. Since I started to use setMethodS3() for *all* (hundreds, maybe
thousands) of my method definitions including default function, that is,
since spring 2001, I *never* had to update a single method because of naming
conflicts or argument conflicts. I can use my hours for other things (as
working on Friday evening ;) ). (The only thing "issue" is that R CMD CHECK
of course complains about mismatching arguments between generic functions
and other). 

Best wishes

Henrik

> -- 
> Brian D. Ripley,                  ripley at stats.ox.ac.uk
> Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
> University of Oxford,             Tel:  +44 1865 272861 (self)
> 1 South Parks Road,                     +44 1865 272866 (PA)
> Oxford OX1 3TG, UK                Fax:  +44 1865 272595
-------------- next part --------------
----------------------------------------------------
CRAN/RQuantLib_0.1.10.tar.gz
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("EuropeanOptionImpliedVolatility", x, ...)
--
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("AmericanOptionImpliedVolatility", x, ...)
--
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("EuropeanOption", x, ...)
--
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("AmericanOption", x, ...)
--
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("BinaryOption", x, ...)
--
  #if (is.null(class(x)))
  #  class(x) <- data.class(x)
  #UseMethod("BarrierOption", x, ...)

----------------------------------------------------
CRAN/XML_0.95-6.tar.gz
function(element, name, pos=NULL)
{
 UseMethod("dtdElementValidEntry", element) # , name, pos)
--
function(node, full = FALSE)
{
  UseMethod("xmlName", node)
--
function(node)
{
  UseMethod("xmlAttrs", node)
--
function(obj)
{
 UseMethod("xmlSize", obj)

----------------------------------------------------
CRAN/Zelig_2.0-9.tar.gz
    class(x) <- x$zelig.call$model
    if (exists(paste("plot.zelig", x$zelig.call$model, sep = ".")))
      UseMethod("plot.zelig", x)
--
sim <- function(object, x, ...) 
  UseMethod("sim", x)
--
summarize <- function(x, ...)
  UseMethod("summarize", x)

----------------------------------------------------
CRAN/car_1.0-13.tar.gz

Anova<-function(mod, ...){
    UseMethod("Anova", mod)
--
scatterplot<-function(x, ...){
    # last modified 28 Jan 2001 by J. Fox
    UseMethod("scatterplot", x)

----------------------------------------------------
CRAN/gam_0.92.tar.gz
			scales[i] <- plot.preplot.gam(x[[i]], y = NULL, 
				residuals, rugplot, se, scale, fit, ...)
		#			scales[i] <- UseMethod("plot",x[[i]])

----------------------------------------------------
CRAN/genetics_1.1.1.tar.gz

LD <- function(g1,...)
  UseMethod("LD",g1)

----------------------------------------------------
CRAN/ipred_0.8-0.tar.gz
# $Id: bagging.R,v 1.18 2003/03/31 08:44:16 peters Exp $

bagging <- function(formula, data, ...) UseMethod("bagging", data)
--
  if(is.null(class(y)))
    class(y) <- data.class(y)
  UseMethod("bootest", y)
--
  if(is.null(class(y)))
    class(y) <- data.class(y)
  UseMethod("cv", y)
--
}

errorest <- function(formula, data, ...) UseMethod("errorest", data)
--


inbagg <- function(formula, data, ...) UseMethod("inbagg", data)
--
# $Id: inclass.R,v 1.30 2003/07/22 14:56:31 peters Exp $

inclass <- function(formula, data, ...) UseMethod("inclass", data)
--
    class(y) <- data.class(y)
#  UseMethod("ipredbagg", y, ...)
  UseMethod("ipredbagg", y)

----------------------------------------------------
CRAN/leaps_2.7.tar.gz

regsubsets<-function(x,...){
  UseMethod("regsubsets",x)

----------------------------------------------------
CRAN/maxstat_0.7-7.tar.gz

maxstat.test <- function(formula, data, ...) 
  UseMethod("maxstat.test", data)

----------------------------------------------------
CRAN/mimR_1.2.2.tar.gz
}

toMIM <- function(data) UseMethod("toMIM", data)

----------------------------------------------------
CRAN/pastecs_1.2-0.tar.gz
"extract" <-
function (e, n, ...)
	UseMethod("extract", e, n, ...)
--
"specs" <-
function(x, ...)
	UseMethod("specs", x, ...)

----------------------------------------------------
CRAN/sem_0.8-0.tar.gz
sem <- function(ram, ...){
    if (is.character(ram)) class(ram) <- 'mod'
    UseMethod('sem', ram)

----------------------------------------------------
CRAN/sna_0.44-1.tar.gz

print.bbnam<-function(x,...){
   UseMethod("print",x)
--

print.summary.bbnam<-function(x,...){
   UseMethod("print",x)
--

plot.bbnam<-function(x,mode="density",intlines=TRUE,...){
   UseMethod("plot",x)



More information about the R-devel mailing list