[R] The end of Matlab
Gabor Grothendieck
ggrothendieck at gmail.com
Fri Dec 12 16:21:44 CET 2008
Here is how to emulate matlab end in R in the case of matrices.
Rather than redefine the matrix class (which would be a bit intrusive) we
just define a subclass of matrix called matrix2. Note in the examples that
matrix2 survives some operations such as + but not others such as crossprod
so in those one would have to coerce back to matrix2 using as.matrix2.
as.matrix2 <- function(x, ...) UseMethod("as.matrix2")
as.matrix2.default <- function(x, ...) {
do.call(structure, list(x, ...,
class = c("matrix2", setdiff(class(x), "matrix2"))))
}
matrix2 <- function(data, ...) as.matrix2(matrix(data, ...))
"[.matrix2" <- function(x, i, j, ...) {
i <- if (missing(i)) TRUE
else eval.parent(do.call(substitute, list(substitute(i), list(end = nrow(x)))))
j <- if (missing(j)) TRUE
else eval.parent(do.call(substitute, list(substitute(j), list(end = ncol(x)))))
.subset(x, i, j, ...)
}
> # test
> m <- matrix2(1:12, 3, 4)
> # matrix2 survives the + operation
> class(m+2)
[1] "matrix2" "matrix"
> # but not crossprod
> class(crossprod(m))
[1] "matrix"
> # coercing back
> as.matrix2(crossprod(m))
[,1] [,2] [,3] [,4]
[1,] 14 32 50 68
[2,] 32 77 122 167
[3,] 50 122 194 266
[4,] 68 167 266 365
attr(,"class")
[1] "matrix2" "matrix"
>
> # example of using end
> m[2:end, 2:end]
[,1] [,2] [,3]
[1,] 5 8 11
[2,] 6 9 12
On Thu, Dec 11, 2008 at 9:45 PM, Mike Rowe <mwrowe at gmail.com> wrote:
> Greetings!
>
> I come to R by way of Matlab. One feature in Matlab I miss is its
> "end" keyword. When you put "end" inside an indexing expression, it
> is interpreted as the length of the variable along the dimension being
> indexed. For example, if the same feature were implemented in R:
>
> my.vector[5:end]
>
> would be equivalent to:
>
> my.vector[5:length(my.vector)]
>
> or:
>
> this.matrix[3:end,end]
>
> would be equivalent to:
>
> this.matrix[3:nrow(this.matrix),ncol(this.matrix)] # or
> this.matrix[3:dim(this.matrix)[1],dim(this.matrix)[2]]
>
> As you can see, the R version requires more typing, and I am a lousy
> typist.
>
> With this in mind, I wanted to try to implement something like this in
> R. It seems like that in order to be able to do this, I would have to
> be able to access the parse tree of the expression currently being
> evaluated by the interpreter from within my End function-- is this
> possible? Since the "[" and "[[" operators are primitive I can't see
> their arguments via the call stack functions...
>
> Anyone got a workaround? Would anybody else like to see this feature
> added to R?
>
> Thanks,
> Mike
>
> ______________________________________________
> R-help at r-project.org mailing list
> 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