[R] Calling any method within default method!

Rui Barradas ru|pb@rr@d@@ @end|ng |rom @@po@pt
Fri May 31 12:40:19 CEST 2019


Hello,

Inline.

Às 10:06 de 31/05/19, Rui Barradas escreveu:
> Hello,
> 
> Your foo.default is wrong in:
> 
> 1) The general principle. S3 methods dispatch on the class attribute, 
> you cannot expect to set that attribute in foo.default
> 
>   and have it call/dispatch
>   and have it call/dispatch
>   and ...

Let me make this more clear.
Your foo.default, with an extra code line right after assigning the 
class to obj, print(class(obj)), outputs the following.


[1] "foo.brazil"
[1] "foo.brazil"
[1] "foo.brazil"
[1] "foo.brazil"
<--- etc --->
[1] "foo.brazil"
[1] "foo.brazil"
[1] "foo.brazil"
[1] "foo.brazil"
Error: C stack usage  7972260 is too close to the limit


It will never reach the methods you need. But if you correct the typo 
and assign like it is below, it will work as expected.


foo <- function (x, ...) UseMethod ('foo')
foo.default <- function(x, a = 10, b = NULL, cc = 2, dd = 3,
                        type = c ('brazil', 'argentina'), ...){

   ty <- match.arg(type)

   obj <- list(a = a, b = b, cc = cc, dd = dd)
   class (obj) <- ty
   res <- foo(x = obj, ...)
   res
}
foo.brazil <- function(x, ...){
   a <- x$a
   cc <- x$cc
   res <- a + cc
   res
}
foo.argentina <- function(x, ...){
   cc <- x$cc
   dd <- x$dd
   res <- sqrt(cc + dd)
   res
}

foo(a = 1)
#[1] 3

foo(a = 1, type = "argentina")
#[1] 2.236068


Hope this helps,

Rui Barradas




> 
> 2) Even if this were possible, your assignment of the class attribute is 
> wrong, you assign "foo.brazil" and "foo.argentina" so the methods to be 
> called would be, respectively,
> 
> foo.foo.brazil
> foo.foo.argentina
> 
> Nonsense! But in fact it's just a typo.
> 
> Try assigning just "brazil" or "argentina" and error 1) above (not very 
> well explained, BTW) will still occur.
> 
> 
> A possible solution is to have a different generic, bar(), with methods 
> bar.brazil and bar.argentina. Something like this:
> 
> 
> foo <- function (x, ...) UseMethod ('foo')
> 
> foo.default <- function(x, a = 10, b = NULL, cc = 2, dd = 3,
>                          type = c('brazil', 'argentina'), ...){
> 
>    ty <- match.arg(type)
> 
>    obj <- list(a = a, b = b, cc = cc, dd = dd)
>    class (obj) <- ty
>    res <- bar(x = obj, ...)
>    res
> }
> 
> bar <- function (x, ...) UseMethod ('bar')
> bar.brazil <- function(x, ...){
>    a <- x$a
>    cc <- x$cc
>    res <- a + cc
>    res
> }
> 
> bar.argentina <- function(x, ...){
>    cc <- x$cc
>    dd <- x$dd
>    res <- sqrt(cc + dd)
>    res
> }
> 
> foo(a = 1)
> #[1] 3
> 
> foo(a = 1, type = 'argentina')
> #[1] 2.236068
> 
> 
> Hope this helps,
> 
> Rui Barradas
> 
> 
> Às 00:34 de 29/05/19, Ivan Bezerra Allaman escreveu:
>> Good night dear!
>> For years I have a problem that I have avoided with the use of the switch
>> function, but now I want to solve by following the good practices of 
>> object
>> orientation (OOP).
>> My function was created to generate experiments according to some input
>> parameters. Therefore, the first argument does not have a class 
>> defined as
>> "data.frame", "matrix", etc., so that from the generic, specific 
>> methods can
>> be called.
>> I made a simple example to show my problem.
>>
>> foo <- function (x, ...) UseMethod ('foo')
>>
>> foo.default <- function(x,
>>                          a = 10,
>>                          b = NULL,
>>                          cc = 2,
>>                          dd = 3,
>>                          type = c ('brazil', 'argentina'),
>>                          ...){
>>
>>    ty <- match.arg(type)
>>
>>    obj <- list(a = a,
>>                   b = b,
>>                   cc = cc,
>>                   dd = dd)
>>    class (obj) <- paste ('foo',
>>                                     ty,
>>                                    sep = '.')
>>
>>    res <- foo(x = obj, ...)
>> }
>>
>> foo.brazil <- function(x, ...){
>>    a <- x$a
>>    cc <- x$cc
>>    res <- a + cc
>>    return (res)
>> }
>>
>> foo.argentina <- function(x, ...){
>>    cc <- x$cc
>>    dd <- x$dd
>>    res <- sqrt(cc + dd)
>>    return (res)
>> }
>>
>> foo(a = 1)
>>
>> If anyone has any light I thank them immensely.
>>
> 
> ______________________________________________
> R-help using r-project.org mailing list -- To UNSUBSCRIBE and more, see
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide 
> http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.



More information about the R-help mailing list