Where the generic and the method have different arguments, there is a 
local version of the method that must be called, with argument 
matching.  In your call, R's behavior is to pass down the missing 
argument from the generic.  (Your explicit empty argument is 
intrinsically different in R from mygen("aa", z="bb"), and that has 
nothing to do with methods.)

I'm on your side here in principle, because the default behavior in the 
method should (to my intuition) always override that in the generic.  
But it may be hard to define behavior that is consistent with R's semantics.

Where the generic and the method have the same arguments, no rematching 
is done, but defaults from the method override those in the generic.  
This is indeed special code, installed at user request and it seems 
reasonable--why else have a default value in the method?  At the moment, 
it does not happen if the generic has no default expression, but in 
principle it would be nice to have the default from the method anyway.  
BUT  this only applies if the generic has the same argument list as the 
method.

So in the case that the arguments are the same for generic and method, 
yes there is a difference between calls to generics and calls, with 
re-matching of arguments, to two regular functions.  In the generic 
case, the default from the method completely overrides that from the 
generic.  The behavior you seem to be advocating would keep both 
defaults, requiring either rematching arguments or some special mechanism.

I'm not against cleaning up the semantics but there would need to be a 
clear proposal that wouldn't impose a serious penalty (for example, 
always rematching the arguments even when the formal arguments are 
identical could be such a penalty).

Herve Pages wrote:
> John Chambers wrote:
>   
>> This has essentially nothing to do with methods, but rather with the
>> treatment of missing arguments.
>>
>> Consider:
>>     
>>> foo <- function(x,...)bar(x,...)
>>> bar <- function(x, y=12, z, ...) {cat(missing(y), "\n"); cat(y, "\n")}
>>>       
>> This is the same argument-matching as your example, since the generic
>> and method have different formal arguments.  And indeed,
>>
>>     
>>> foo("a",,z=99)
>>>       
>> TRUE
>> Error in cat(y, "\n") : argument is missing, with no default
>>
>> The error message is correct, but the argument in question is not "y"
>> but "..1".  This is constructed and passed down as a special R object
>> representing "missing-argument-with-no-default".   (Splus would have
>> worked as you expected, because missingness there is a property of the
>> function call, not of the object corresponding to the formal argument.)
>>     
>
> Thanks John for the clarification! I can see why, _technically speaking_, 
> things
> behave how they behave.
>
> Note that what happens with default arguments in methods is not always the 
> same
> as with normal functions so it's not always possible to predict what is 
> actually
> going to happen... Here is an example:
>
> 1) Default arg in the method:
>
>    o generic + method:
>      > bar <- function(x, y=12, z) {cat(missing(y), "\n"); cat(x, y, z, "\n")}
>      > setGeneric("mygen", signature=c("x", "z"), function(x, y, z) 
> standardGeneric("mygen"))
>      > setMethod("mygen", c("ANY", "ANY"), bar)
>      > mygen("aa", , "bb")
>      TRUE
>      Error in cat(x, y, z, "\n") : argument "y" is missing, with no default
>
>    o normal functions:
>      > foo <- function(x, y, z) bar(x, y, z)
>      > foo("aa", ,"bb")
>      TRUE
>      Error in cat(x, y, z, "\n") : argument "y" is missing, with no default
>
>    Behaviour is the same.
>
> 2) Default arg in the generic:
>
>    o generic + method: example 1) shows that if I want a default value
>      for y, it should be put in the generic rather than in the method:
>      > bar <- function(x, y, z) {cat(missing(y), "\n"); cat(x, y, z, "\n")}
>      > setGeneric("mygen", signature=c("x", "z"), function(x, y=12, z) 
> standardGeneric("mygen"))
>   
But now you're changing the game, because generic and method now have 
identical argument lists.
>      > setMethod("mygen", c("ANY", "ANY"), bar)
>      > mygen("aa", , "bb")
>      TRUE
>      aa 12 bb
>
>    o normal functions:
>      > foo <- function(x, y=12, z) bar(x, y, z)
>      > foo("aa", ,"bb")
>      FALSE
>      aa 12 bb
>
>    Behaviour is _almost_ the same!
>
> 3) Default arg in the generic _and_ in the method:
>
>    o generic + method:
>      > bar <- function(x, y=999, z) {cat(missing(y), "\n"); cat(x, y, z, 
> "\n")}
>      > setMethod("mygen", c("ANY", "ANY"), bar)
>      > mygen("aa", , "bb")
>      TRUE
>      aa 999 bb
>
>      Not what I would expect

Here you want a difference between this and mygen("aa", z="bb")?  OK, 
but in your original post, it looked like you did not want such a 
difference.
>    o normal functions:
>      > foo("aa", ,"bb")
>      FALSE
>      aa 12 bb
>
>      Much better.
>
> I'm sure there is a _technical_ explanation for this (with probably some lazy 
> evaluation
> involved) but I find the current behaviour confusing and very hard to predict.
>
> Cheers,
> H.
>
>
>   
>> Herve Pages wrote:
>>     
>>> Hi,
>>>
>>>
>>> Strange things happen with missing args in S4 methods:
>>>
>>>   > setGeneric("mygen", signature="x", function(x, ...)
>>> standardGeneric("mygen"))
>>>   [1] "mygen"
>>>
>>>   > setMethod("mygen", "character", function(x, y=12, z, ...)
>>> {cat(missing(y), "\n"); cat(y, "\n")})
>>>   [1] "mygen"
>>>
>>>   > mygen("aa", z=99)
>>>   TRUE
>>>   12
>>>
>>>   > mygen("aa", , 99)
>>>   TRUE
>>>   Error in cat(y, "\n") : argument is missing, with no default
>>>                                       ^^^^^^^       ^^^^^^^^^^
>>>                                        TRUE          NOT TRUE!
>>>
>>>
>>> For "normal" functions, things work as expected:
>>>
>>>   > myfun <- function(x, y=12, z, ...) {cat(missing(y), "\n"); cat(y,
>>> "\n")}
>>>
>>>   > myfun("aa", z=99)
>>>   TRUE
>>>   12
>>>
>>>   > myfun("aa", , 99)
>>>   TRUE
>>>   12
>>>
>>> And with S3 generics too:
>>>
>>>   > dd <- data.frame(aa=letters[1:9], ii=9:1)
>>>   > head(dd, z="ignored")
>>>     aa ii
>>>   1  a  9
>>>   2  b  8
>>>   3  c  7
>>>   4  d  6
>>>   5  e  5
>>>   6  f  4
>>>
>>>   > head(dd, , "ignored")
>>>     aa ii
>>>   1  a  9
>>>   2  b  8
>>>   3  c  7
>>>   4  d  6
>>>   5  e  5
>>>   6  f  4
>>>
>>> Cheers,
>>> H.
>>>
>>> ______________________________________________
>>> R-devel@r-project.org mailing list
>>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>>
>>>   
>>>       
>
>   

        [[alternative HTML version deleted]]

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to