# File src/library/base/R/matrix.R # Part of the R package, http://www.R-project.org # # Copyright (C) 1995-2012 The R Core Team # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # A copy of the GNU General Public License is available at # http://www.r-project.org/Licenses/ matrix <- function(data=NA, nrow=1, ncol=1, byrow=FALSE, dimnames=NULL) { ## avoid copying to strip attributes in simple cases if (is.object(data) || !is.atomic(data)) data <- as.vector(data) ## NB: the defaults are not really nrow=1, ncol=1: missing values ## are treated differently, using length(data). .Internal(matrix(data, nrow, ncol, byrow, dimnames, missing(nrow), missing(ncol))) } nrow <- function(x) dim(x)[1L] ncol <- function(x) dim(x)[2L] NROW <- function(x) if(length(d <- dim(x))) d[1L] else length(x) NCOL <- function(x) if(length(d <- dim(x)) > 1L) d[2L] else 1L rownames <- function(x, do.NULL = TRUE, prefix = "row") { dn <- dimnames(x) if(!is.null(dn[[1L]])) dn[[1L]] else { nr <- NROW(x) if(do.NULL) NULL else if(nr > 0L) paste0(prefix, seq_len(nr)) else character() } } `rownames<-` <- function(x, value) { if(is.data.frame(x)) { row.names(x) <- value } else { dn <- dimnames(x) if(is.null(dn)) { if(is.null(value)) return(x) if((nd <- length(dim(x))) < 1L) stop("attempt to set 'rownames' on an object with no dimensions") dn <- vector("list", nd) } if(length(dn) < 1L) stop("attempt to set 'rownames' on an object with no dimensions") if(is.null(value)) dn[1L] <- list(NULL) else dn[[1L]] <- value dimnames(x) <- dn } x } colnames <- function(x, do.NULL = TRUE, prefix = "col") { if(is.data.frame(x) && do.NULL) return(names(x)) dn <- dimnames(x) if(!is.null(dn[[2L]])) dn[[2L]] else { nc <- NCOL(x) if(do.NULL) NULL else if(nc > 0L) paste0(prefix, seq_len(nc)) else character() } } `colnames<-` <- function(x, value) { if(is.data.frame(x)) { names(x) <- value } else { dn <- dimnames(x) if(is.null(dn)) { if(is.null(value)) return(x) if((nd <- length(dim(x))) < 2L) stop("attempt to set 'colnames' on an object with less than two dimensions") dn <- vector("list", nd) } if(length(dn) < 2L) stop("attempt to set 'colnames' on an object with less than two dimensions") if(is.null(value)) dn[2L] <- list(NULL) else dn[[2L]] <- value dimnames(x) <- dn } x } row <- function(x, as.factor=FALSE) { if(as.factor) { labs <- rownames(x, do.NULL=FALSE, prefix="") res <- factor(.Internal(row(dim(x))), labels=labs) dim(res) <- dim(x) res } else .Internal(row(dim(x))) } col <- function(x, as.factor=FALSE) { if(as.factor) { labs <- colnames(x, do.NULL=FALSE, prefix="") res <- factor(.Internal(col(dim(x))), labels=labs) dim(res) <- dim(x) res } else .Internal(col(dim(x))) } crossprod <- function(x, y=NULL) .Internal(crossprod(x,y)) tcrossprod <- function(x, y=NULL) .Internal(tcrossprod(x,y)) t <- function(x) UseMethod("t") ## t.default is t.data.frame <- function(x) { x <- as.matrix(x) NextMethod("t") } ## as.matrix is in "as"