[R] zero-offset matrices

Prof Brian Ripley ripley at stats.ox.ac.uk
Tue Mar 2 15:58:24 CET 1999


> Date: Tue, 2 Mar 1999 12:18:46 +0000 (GMT)
> From: Jonathan Rougier <J.C.Rougier at durham.ac.uk>
> To: r-help at stat.math.ethz.ch
> Subject: [R] zero-offset matrices
> 
> Has anyone written subscripting methods for matrices which are indexed
> from zero? i.e. functions such as "[.zoffset" and "[<-.zoffset" which
> would allow, given an appropriate function "zmatrix"
> 
> "zmatrix" <- function(...)
> {
> 	robj <- matrix(...)
> 	class(robj) <- "zoffset"
> 	robj
> }
> 
> fred <- zmatrix(1:20, 4, 5)
> fred[0, 4]		# would be 17
> fred[3, ] <- NA		# would set the last row to NA
> 

No, but should it not be very easy? Just check if the subscript is
numeric, add 1, call NextMethod? Let's see:

"[.zoffset"  <- function(x, i, j, drop=F)
{
  if(!missing(i) && is.numeric(i)) i <- i+1
  if(!missing(j) && is.numeric(j)) j <- j+1
  NextMethod("[")
}
works.  But

"[<-.zoffset"  <- function(x, i, j, value)
{
  if(!missing(i) && is.numeric(i)) i <- i+1
  if(!missing(j) && is.numeric(j)) j <- j+1
  NextMethod("[<-")
}
works in S but not in R. (Which I think is a bug.) I next tried

"[<-.zoffset"  <- function(x, i, j, value)
{
  Call <- match.call()
  if(!missing(i) && is.numeric(i)) Call$i <- i+1
  if(!missing(j) && is.numeric(j)) Call$j <- j+1
  Call$x <- unclass(Call$x)
  Call[[1]] <- as.name("[<-")
  structure(eval(Call), class=class(x))
}

which works only if x and y are not missing, as "[<-"(x=x, i=i,
value=value) does not do what I expected (it takes j=1). You need
"[<-"(x=x, i=i, j=, value=value) and I could not construct that in R
easily. So I resorted to doing this by hand:

"[<-.zoffset"  <- function(x, i, j, value)
{
  if(!missing(i) && is.numeric(i)) i <- i+1
  if(!missing(j) && is.numeric(j)) j <- j+1
  y <- unclass(x)
  if(missing(i)) {
    if(missing(j)) y[] <- value else y[, j] <- value
  } else {
    if(missing(j)) y[i,] <- value else y[i, j] <- value
  }
  structure(y, class=class(x))
}

So perhaps someone who really understands R will tell me what is going on here.

-- 
Brian D. Ripley,                  ripley at stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272860 (secr)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595

-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._



More information about the R-help mailing list