[Rd] Creating a vector class

John Chambers jmc at research.bell-labs.com
Fri May 30 10:14:42 MEST 2003


Sounds like a nice example.  Just a quick comment on one question before
I have to run, will try to react more later.

John

Duncan Murdoch wrote:
> 
> I'm trying to create a package for working on orientation data, i.e.
> data where the observations are 3D rotations.
> 
> There are several different representations of orientations in common
> use:  SO(3) matrices, Euler angles, unit quaternions, etc.  One thing
> I'd like is to make it convenient to work in any representation, and
> have conversions to others done as needed.
> 
> I'm trying to do all of this in S4 classes.  Here's the current class
> structure I'm using; please let me know if there's something wrong
> with this:
> 
> The base class is abstract.  All representations will deal with
> vectors of orientations, but at this level I don't know how that will
> be implemented:
> 
> setClass('orientation')
> setIs('orientation', 'vector')
> 
> First questions:  is this the way to say that orientations behave as
> vectors?  Do I need to say that?  Should I say that?
> 
> One representation is as an SO(3) matrix (i.e. a 3x3 matrix with
> determinant 1).  I have a descendant class that stores these in a
> 3 x 3 x n array:
> 
> setClass('rotmatrix', representation(x = 'array'))
> setIs('rotmatrix','orientation')
> 
> rotmatrix <- function(a) {
>     d <- dim(a)
>     if (length(d) < 3) d <- c(d,1)
>     a <- array(a, d)
>     stopifnot(dim(a)[1] == 3, dim(a)[2] == 3)
>     new('rotmatrix', x = a)
> }
> 
> Other representations have other storage methods, e.g.
> 
> setClass('quaternion', representation(x = 'matrix'))
> setIs('quaternion', 'orientation')
> 
> Now I want to make sure these work as vectors.  I don't need to define
> a '[' method for the abstract base class, do I?  I originally set this
> definition for the rotmatrix class:
> 
> setMethod('[', 'rotmatrix',
>     def = function(x, i) rotmatrix(x at x[,,i,drop=FALSE])
> )
> 
> However, this gives warnings:
> 
> >In method for function "[": Expanding the signature to
> >include omitted arguments in definition: j = "missing",
> >drop = "missing"
> 
> I notice in the setMethod example the right way to do it:
> 
> setMethod('[', 'rotmatrix',
>     function(x, i, j, ..., drop) rotmatrix(x at x[,,i,drop=FALSE])
> )
> 
> But where are the meanings for j and drop defined?  Even if I don't
> declare orientation to be a vector, I get this warning, so where is it
> coming from?  Is it good or bad to say that orientation is a vector?
> What implications does it have?

Actually, even though the message was a "warning", it really says what I
think you want to do.

The arguments j and drop arise in matrix or matrix-like objects
(data.frame) and are in the generic so that methods can be dispatched
(e.g.) on the column index argument.

But in your case, indeed they had BETTER be missing, assuming they're
meaningless in this example.

So you could just accept the warning as a harmless nag (and maybe it
should be a message rather than a warning in this case, but in other
functions the omission might in fact have been a mistake).

Or to be fastidious, you could supply the arguments with class "missing"
in the signature to make explicit that the user had better not try to
supply them.

 setMethod('[', signature(x='rotmatrix', j= 'missing', drop =
'missing'),
     def = function(x, i) rotmatrix(x at x[,,i,drop=FALSE])
 )

> 
> Duncan Murdoch
> 
> ______________________________________________
> R-devel at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-devel

-- 
John M. Chambers                  jmc at bell-labs.com
Bell Labs, Lucent Technologies    office: (908)582-2681
700 Mountain Avenue, Room 2C-282  fax:    (908)582-3340
Murray Hill, NJ  07974            web: http://www.cs.bell-labs.com/~jmc



More information about the R-devel mailing list