[Rd] setMethod("c") [was: setMethod("Summary")]
Robin Hankin
r.hankin at noc.soton.ac.uk
Wed Sep 6 10:21:00 CEST 2006
Dear All
thank you for your continued patience and help.
The example in the Green Book is
setGeneric("max",
function(x, ..., na.rm=FALSE){
if(nDotArgs(...)>0){
max(c(max(x, na.rm=na.rm), max(..., na.rm=na.rm)))
} else {
standardGeneric("max")
}
}
)
The point of this example is to implement a tail recursion. But it
isn't applicable
to c() because it is a primitive function and the generic function
cannot be changed:
setGeneric("c",
function(x, ...){
z <- list(...)
if(length(z)>0){
return(c(x, c(...)))
} else {
return(standardGeneric("c"))
}
}
)
gives the following error:
Error in setGeneric("c", function(x, ...) { :
'c' is a primitive function; methods can be defined, but the
generic function is implicit, and cannot be changed.
OK, plan B (or should that be plan A?) is to define cPair() and call
that .
Minimal self-contained code follows
setClass("brob",
representation = representation
(x="numeric",positive="logical"),
prototype = list(x=numeric(),positive=logical())
)
"brob" <- function(x,positive){
if(missing(positive)){
positive <- rep(TRUE,length(x))
}
if(length(positive)==1){
positive <- rep(positive,length(x))
}
new("brob",x=x,positive=positive)
}
is.brob <- function(x){is(x,"brob")}
as.brob <- function(x){
if(is.brob(x)){
return(x)
} else {
return(brob(log(abs(x)),x>0))
}
}
cWithMethods <- function(x, ..., recursive=TRUE) {
if(nargs()<3){
return(cPairOfBrobs(x, ...))
} else {
return(cPairOfBrobs(x, cWithMethods(...)))
}
}
cPairOfBrobs <- function(x,y){
x <- as.brob(x)
y <- as.brob(y)
brob(c(x at x,y at x),c(x at positive,y at positive))
}
setMethod("c",signature("brob"),cWithMethods)
But this has the same problem as before; if x is a brob,
then c(x,1) is fine but c(1,x) isn't:
x <- new("brob",x=pi,positive=T)
c(x,1)
An object of class "brob"
Slot "x":
[1] 3.141593 0.000000
Slot "positive":
[1] TRUE TRUE
> c(1,x)
[[1]]
[1] 1
How do I tell setMethod("c", ...) to call the appropriate functions
if any object passed to c()
is a brob?
On 5 Sep 2006, at 16:47, John Chambers wrote:
> (Before someone else can embarrass me with the reference)
>
> There is a variant on the c() example discussed in "Programming with
> Data", page 351, for the function max().
>
> John
>
> John Chambers wrote:
>> It's all very well to go on about efficiency, but the purpose of
>> statistical computing is insight into data, not saving CPU cycles (to
>> paraphrase Dick Hamming).
>>
>> S3 methods do some things fine; other tasks need more
>> flexibility. One
>> should ask what's important in a particular application and try to
>> find
>> tools that match the needs well.
>>
>> Now, the c() function. This has been discussed in various forms (and
>> languages) for some time. As I remember and as far as I know, the
>> only
>> really general way to ensure dispatch on _any_ applicable argument
>> is to
>> turn the computation into a pair-wise one and define the methods
>> (NOT S3
>> methods) for the two arguments of the pairwise function.
>>
>> I won't try to reproduce the details off the top of my head (if I
>> locate
>> a reference I'll pass it on), but very roughly the idea is to say
>> something like
>>
>> cWithMethods <- function(x, ...) {
>> if(nargs()<3)
>> cPair(x,...)
>> else
>> cPair(x, cWithMethods(...))
>> }
>>
>> and then write methods for cPair().
>>
>> John
>>
>> Robin Hankin wrote:
>>
>>> Hello everybody.
>>>
>>> I didn't see Franklin's first message; sorry.
>>>
>>> Bearing in mind Professor Ripley's comments
>>> on the efficiency of S4 vs S3, I'm beginning to think I
>>> should just stick with S3 methods for my brob objects. After
>>> all, S3 was perfectly adequate for the onion package.
>>>
>>> Notwithstanding that, here's my next problem. I want to define a
>>> brob method for "c". Using the example in package "arules" as a
>>> template (I couldn't see one in Matrix), I have
>>>
[snip]
>>>
>>>
>>> Now, this works for something like
>>>
>>>> x <- new("brob",x=pi,positive=T)
>>>> c(x,x)
>>>
>>> but c(1,x) isn't dispatched to my function. How to
>>> deal cleanly with this case? Perhaps if any argument
>>> to c() is a brob object, I would like to coerce them all to brobs.
>>> Is this possible?
>>>
>>>
--
Robin Hankin
Uncertainty Analyst
National Oceanography Centre, Southampton
European Way, Southampton SO14 3ZH, UK
tel 023-8059-7743
More information about the R-devel
mailing list