Hi
I am having difficulty with setMethod().  I have a "brob" class of  
objects whose
representation has two slots: "x" and "positive".  Slot
"x"  (double)
holds the log
of a number and slot "positive" (logical) its sign.   The idea is  
that large numbers
can be handled.
I'm trying to implement a log() method using an analogue of the  
setMethod() example
for polynomials on page 117 of V&R.  abs() works [I think], but log()  
doesn't:
[transcript follows, source for  the classes below]
 > a <- as.brob((-4:4 )+0.4)
 > a
An object of class "brob"
Slot "x":
[1]  1.2809338  0.9555114  0.4700036 -0.5108256 -0.9162907   
0.3364722  0.8754687
[8]  1.2237754  1.4816045
Slot "positive":
[1] FALSE FALSE FALSE FALSE  TRUE  TRUE  TRUE  TRUE  TRUE
 > abs(a)
An object of class "brob"
Slot "x":
[1]  1.2809338  0.9555114  0.4700036 -0.5108256 -0.9162907   
0.3364722  0.8754687
[8]  1.2237754  1.4816045
Slot "positive":
[1] TRUE TRUE TRUE TRUE TRUE TRUE TRUE TRUE TRUE
# This works: each element is now positive.
 > log(a)
Error in log(x) : Non-numeric argument to mathematical function
 >
What's wrong with my setMethod() call below?
setClass("brob",
          representation = representation 
(x="numeric",positive="logical"),
          prototype      = list(x=numeric(),positive=logical())
          )
setAs("brob", "numeric", function(from){
   out <- exp(from at x)
   out[!from at positive] <- -out[!from at positive]
   return(out)
}
       )
setMethod("as.numeric",signature(x="brob"),function(x){as(x,"numeric")})
is.brob <- function(x){is(x,"brob")}
"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)
}
as.brob <- function(x){
   brob(log(abs(x)),x>0)
}
setMethod("Math", "brob",
           function(x){
             switch(.Generic,
                    abs    = brob(x at x),
                    log    = { out <- x at x
                               out[!x at positive] <- NaN
                               out
                             },
                    acos   =,
                    acosh  =,
                    asin   =,
                    asinh  =,
                    atan   =,
                    atanh  =,
                    ceiling=,
                    cos    =,
                    cosh   =,
                    cumsum =,
                    exp    =,
                    floor  =,
                    gamma  =,
                    lgamma =,
                    sin    =,
                    sinh   =,
                    tan    =,
                    tanh   =,
                    trunc  = as.brob(callGeneric(as.numeric(x))),
                    stop(paste(.Generic, "not allowed on  
Brobdingnagian numbers"))
                      )
           }
           )
--
Robin Hankin
Uncertainty Analyst
National Oceanography Centre, Southampton
European Way, Southampton SO14 3ZH, UK
  tel  023-8059-7743
Hi Robin,
from reading ?Math:
     Note: currently those members which are not primitive functions
     must have been converted to S4 generic functions (preferably
     _before_ setting an S4 group generic method) as it only sets
     methods for known S4 generics.  This can be done by a call to
     'setGeneric', for example 'setGeneric("round",
group="Math2")'.
so
setGeneric("log", group="Math")
before setMethod("Math", ...) seems to do the trick (perhaps at the
expense of adding explicit S4 method dispatch to log). The difference
between abs and log is apparent from looking at their definitions
> abs
.Primitive("abs")> log
function (x, base = exp(1)) 
if (missing(base)) .Internal(log(x)) else .Internal(log(x, base))
<environment: namespace:base>
Hope that removes some uncertainty.
Martin
-- 
Bioconductor
Robin Hankin <r.hankin at noc.soton.ac.uk> writes:
> Hi
>
> I am having difficulty with setMethod().  I have a "brob" class
of
> objects whose
> representation has two slots: "x" and "positive".  Slot
"x"  (double)
> holds the log
> of a number and slot "positive" (logical) its sign.   The idea is
> that large numbers
> can be handled.
>
> I'm trying to implement a log() method using an analogue of the  
> setMethod() example
> for polynomials on page 117 of V&R.  abs() works [I think], but log()  
> doesn't:
>
> [transcript follows, source for  the classes below]
>
>
>
>  > a <- as.brob((-4:4 )+0.4)
>  > a
> An object of class "brob"
> Slot "x":
> [1]  1.2809338  0.9555114  0.4700036 -0.5108256 -0.9162907   
> 0.3364722  0.8754687
> [8]  1.2237754  1.4816045
>
> Slot "positive":
> [1] FALSE FALSE FALSE FALSE  TRUE  TRUE  TRUE  TRUE  TRUE
>
>  > abs(a)
> An object of class "brob"
> Slot "x":
> [1]  1.2809338  0.9555114  0.4700036 -0.5108256 -0.9162907   
> 0.3364722  0.8754687
> [8]  1.2237754  1.4816045
>
> Slot "positive":
> [1] TRUE TRUE TRUE TRUE TRUE TRUE TRUE TRUE TRUE
>
> # This works: each element is now positive.
>
>  > log(a)
> Error in log(x) : Non-numeric argument to mathematical function
>  >
>
>
>
> What's wrong with my setMethod() call below?
>
>
>
>
>
> setClass("brob",
>           representation = representation 
> (x="numeric",positive="logical"),
>           prototype      = list(x=numeric(),positive=logical())
>           )
>
> setAs("brob", "numeric", function(from){
>    out <- exp(from at x)
>    out[!from at positive] <- -out[!from at positive]
>    return(out)
> }
>        )
>
>
setMethod("as.numeric",signature(x="brob"),function(x){as(x,"numeric")})
>
> is.brob <- function(x){is(x,"brob")}
>
> "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)
> }
>
> as.brob <- function(x){
>    brob(log(abs(x)),x>0)
> }
>
> setMethod("Math", "brob",
>            function(x){
>              switch(.Generic,
>                     abs    = brob(x at x),
>                     log    = { out <- x at x
>                                out[!x at positive] <- NaN
>                                out
>                              },
>                     acos   =,
>                     acosh  =,
>                     asin   =,
>                     asinh  =,
>                     atan   =,
>                     atanh  =,
>                     ceiling=,
>                     cos    =,
>                     cosh   =,
>                     cumsum =,
>                     exp    =,
>                     floor  =,
>                     gamma  =,
>                     lgamma =,
>                     sin    =,
>                     sinh   =,
>                     tan    =,
>                     tanh   =,
>                     trunc  = as.brob(callGeneric(as.numeric(x))),
>                     stop(paste(.Generic, "not allowed on  
> Brobdingnagian numbers"))
>                       )
>            }
>            )
>
>
>
>
>
>
> --
> Robin Hankin
> Uncertainty Analyst
> National Oceanography Centre, Southampton
> European Way, Southampton SO14 3ZH, UK
>   tel  023-8059-7743
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel