Intro 2 Matrix
Intro 2 Matrix
Abstract
Linear algebra is at the core of many areas of statistical computing and from its inception the S lan-
guage has supported numerical linear algebra via a matrix data type and several functions and operators,
such as %*%, qr, chol, and solve. However, these data types and functions do not provide direct access
to all of the facilities for efficient manipulation of dense matrices, as provided by the Lapack subroutines,
and they do not provide for manipulation of sparse matrices.
The Matrix package provides a set of S4 classes for dense and sparse matrices that extend the basic
matrix data type. Methods for a wide variety of functions and operators applied to objects from these
classes provide efficient access to BLAS (Basic Linear Algebra Subroutines), Lapack (dense matrix),
CHOLMOD including AMD and COLAMD and Csparse (sparse matrix) routines. One notable char-
acteristic of the package is that whenever a matrix is factored, the factorization is stored as part of the
original matrix so that further operations on the matrix can reuse this factorization.
1 Introduction
The most automatic way to use the Matrix package is via the Matrix() function which is very similar to
the standard R function matrix(),
> library(Matrix)
> M <- Matrix(10 + 1:28, 4, 7)
> M
Such a matrix can be appended to (using cBind() or rBind() with capital “B”) or indexed,
> (M2 <- cBind(-1, M))
1
> M[2, 1]
[1] 12
> M[4, ]
[1] 14 18 22 26 30 34 38
where the last two statements show customary matrix indexing, returning a simple numeric vector each1 .
We assign 0 to some columns and rows to “sparsify” it, and some NAs (typically “missing values” in data
analysis) in order to demonstrate how they are dealt with; note how we can “subassign” as usual, for classical
R matrices (i.e., single entries or whole slices at once),
> M2[, c(2,4:6)] <- 0
> M2[2, ] <- 0
> M2 <- rBind(0, M2, 0)
> M2[1:2,2] <- M2[3,4:5] <- NA
and then coerce it to a sparse matrix,
> sM <- as(M2, "sparseMatrix")
> 10 * sM
[1,] . NA . . . . . .
[2,] -10 NA 150 . . . 310 350
[3,] . . . NA NA . . .
[4,] -10 . 170 . . . 330 370
[5,] -10 . 180 . . . 340 380
[6,] . . . . . . . .
[1] TRUE
[1] TRUE
where the last three calls show that multiplication by a scalar keeps sparcity, as does other arithmetic,
but addition to a “dense” object does not, as you might have expected after some thought about “sensible”
behavior:
> sM + 10
2
Operations on our classed matrices include (componentwise) arithmetic (+, −, ∗, /, etc) as partly seen
above, comparison (>, ≤, etc), e.g.,
> Mg2 <- (sM > 2)
> Mg2
6 x 8 sparse Matrix of class "lgCMatrix"
[1,] . N . . . . . .
[2,] : N | . . . | |
[3,] . . . N N . . .
[4,] : . | . . . | |
[5,] : . | . . . | |
[6,] . . . . . . . .
returning a logical sparse matrix. When interested in the internal structure, str() comes handy, and we
have been using it ourselves more regulary than print()ing (or show()ing as it happens) our matrices;
alternatively, summary() gives output similar to Matlab’s printing of sparse matrices.
> str(Mg2)
Formal class 'lgCMatrix' [package "Matrix"] with 6 slots
..@ i : int [1:16] 1 3 4 0 1 1 3 4 2 2 ...
..@ p : int [1:9] 0 3 5 8 9 10 10 13 16
..@ Dim : int [1:2] 6 8
..@ Dimnames:List of 2
.. ..$ : NULL
.. ..$ : NULL
..@ x : logi [1:16] FALSE FALSE FALSE NA NA TRUE ...
..@ factors : list()
> summary(Mg2)
6 x 8 sparse Matrix of class "lgCMatrix", with 16 entries
i j x
1 2 1 FALSE
2 4 1 FALSE
3 5 1 FALSE
4 1 2 NA
5 2 2 NA
6 2 3 TRUE
7 4 3 TRUE
8 5 3 TRUE
9 3 4 NA
10 3 5 NA
11 2 7 TRUE
12 4 7 TRUE
13 5 7 TRUE
14 2 8 TRUE
15 4 8 TRUE
16 5 8 TRUE
As you see from both of these, Mg2 contains “extra zero” (here FALSE) entries; such sparse matrices may be
created for different reasons, and you can use drop0() to remove (“drop”) these extra zeros. This should
never matter for functionality, and does not even show differently for logical sparse matrices, but the internal
structure is more compact:
3
> Mg2 <- drop0(Mg2)
> str(Mg2@x) # length 13, was 16
For large sparse matrices, visualization (of the sparsity pattern) is important, and we provide image()
methods for that, e.g.,
> data(CAex)
> print(image(CAex, main = "image(CAex)")) # print(.) needed for Sweave
image(CAex)
1.0
0.8
20
0.6
0.4
Row
40 0.2
0.0
−0.2
60
−0.4
20 40 60
Column
Dimensions: 72 x 72
Further, i.e., in addition to the above implicitly mentioned "Ops" operators (+, *,. . . , <=,>,. . . , & which all
work with our matrices, notably in conjunction with scalars and traditional matrices), the "Math"-operations
(such as exp(), sin() or gamma()) and "Math2" (round() etc) and the "Summary" group of functions, min(),
range(), sum(), all work on our matrices as they should. Note that all these are implemented via so called
group methods, see e.g., ?Arith in R. The intention is that sparse matrices remain sparse whenever sensible,
given the matrix classes and operators involved, but not content specifically. E.g., <sparse> + <dense>
gives <dense> even for the rare cases where it would be advantageous to get a <sparse> result.
These classed matrices can be “indexed” (more technically “subset”) as traditional S language (and hence
R) matrices, as partly seen above. This also includes the idiom M [ M hopi hnumi ] which returns simple
vectors,
> sM[sM > 2]
[1] NA NA 15 17 18 NA NA 31 33 34 35 37 38
[1] 0 -1 0 -1 -1 0 NA NA 0 0 0 0 0 0 0 0 0 NA 0 0 0 0 0
[24] NA 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
and “subassign”ment similarly works in the same generality as for traditional S language matrices.
4
1.1 Matrix package for numerical linear algebra
Linear algebra is at the core of many statistical computing techniques and, from its inception, the S language
has supported numerical linear algebra via a matrix data type and several functions and operators, such as
%*%, qr, chol, and solve. Initially the numerical linear algebra functions in R called underlying Fortran
routines from the Linpack (Dongarra et al., 1979) and Eispack (Smith et al., 1976) libraries but over the
years most of these functions have been switched to use routines from the Lapack (Anderson et al., 1999)
library which is the state-of-the-art implementation of numerical dense linear algebra. Furthermore, R can be
configured to use accelerated BLAS (Basic Linear Algebra Subroutines), such as those from the Atlas (Whaley
et al., 2001) project or other ones, see the R manual “Installation and Administration”.
Lapack provides routines for operating on several special forms of matrices, such as triangular matrices
and symmetric matrices. Furthermore, matrix decompositions like the QR decompositions produce multiple
output components that should be regarded as parts of a single object. There is some support in R for
operations on special forms of matrices (e.g. the backsolve, forwardsolve and chol2inv functions) and for
special structures (e.g. a QR structure is implicitly defined as a list by the qr, qr.qy, qr.qty, and related
functions) but it is not as fully developed as it could be.
Also there is no direct support for sparse matrices in R although Koenker and Ng (2003) have developed
the SparseM package for sparse matrices based on SparseKit.
The Matrix package provides S4 classes and methods for dense and sparse matrices. The methods
for dense matrices use Lapack and BLAS. The sparse matrix methods use CHOLMOD (Davis, 2005a),
CSparse (Davis, 2005b) and other parts (AMD, COLAMD) of Tim Davis’ “SuiteSparse” collection of sparse
matrix libraries, many of which also use BLAS.
Todo: triu(), tril(), diag(), ... and as(.,.) , but of course only when they’ve seen a few different
ones.
Todo: matrix operators include %*%, crossprod(), tcrossprod(), solve()
Todo: expm() is the matrix exponential ... ...
Todo: symmpart() and skewpart() compute the symmetric part, (x + t(x))/2 and the skew-symmetric
part, (x - t(x))/2 of a matrix x.
Todo: factorizations include Cholesky() (or chol()), lu(), qr() (not yet for dense)
Todo: Although generally the result of an operation on dense matrices is a dgeMatrix, certain operations
return matrices of special types.
Todo: E.g. show the distinction between t(mm) %*% mm and crossprod(mm).
2 Matrix Classes
The Matrix package provides classes for real (stored as double precision), logical and so-called “pattern”
(binary) dense and sparse matrices. There are provisions to also provide integer and complex (stored as
double precision complex) matrices.
Note that in R, logical means entries TRUE, FALSE, or NA. To store just the non-zero pattern for typical
sparse matrix algorithms, the pattern matrices are binary, i.e., conceptually just TRUE or FALSE. In Matrix,
the pattern matrices all have class names starting with "n" (pattern).
5
dtrMatrix Triangular real matrices in non-packed storage
dtpMatrix Triangular real matrices in packed storage (triangle only)
dpoMatrix Positive semi-definite symmetric real matrices in non-packed storage
dppMatrix ditto in packed storage
Methods for these classes include coercion between these classes, when appropriate, and coercion to the
matrix class; methods for matrix multiplication (%*%); cross products (crossprod), matrix norm (norm);
reciprocal condition number (rcond); LU factorization (lu) or, for the poMatrix class, the Cholesky decom-
position (chol); and solutions of linear systems of equations (solve).
Whenever a factorization or a decomposition is calculated it is preserved as a (list) element in the factors
slot of the original object. In this way a sequence of operations, such as determining the condition number
of a matrix then solving a linear system based on the matrix, do not require multiple factorizations of the
same matrix nor do they require the user to store the intermediate results.
Slots:
2 For efficiency reasons, we use “zero-based” indexing in the Matrix package, i.e., the row indices i are in 0:(nrow(.)-1) and
6
Name: i j Dim Dimnames
Class: integer integer integer list
Extends:
Class "sparseMatrix", directly
Class "Matrix", by class "sparseMatrix", distance 2
Class "mMatrix", by class "Matrix", distance 3
Class "Mnumeric", by class "Matrix", distance 3
Class "replValueSp", by class "Matrix", distance 3
> getClass("dgTMatrix")
Slots:
Extends:
Class "TsparseMatrix", directly
Class "dsparseMatrix", directly
Class "generalMatrix", directly
Class "dMatrix", by class "dsparseMatrix", distance 2
Class "sparseMatrix", by class "dsparseMatrix", distance 2
Class "compMatrix", by class "generalMatrix", distance 2
Class "Matrix", by class "TsparseMatrix", distance 3
Class "mMatrix", by class "Matrix", distance 4
Class "Mnumeric", by class "Matrix", distance 4
Class "replValueSp", by class "Matrix", distance 4
Note that the order of the entries in the (i,j,x) vectors does not matter; consequently, such matrices are
not unique in their representation. 4
7
of which we make use. For this reason, the CsparseMatrix class and subclasses are the principal classes for
sparse matrices in the Matrix package.
The Matrix package provides the following classes for sparse matrices . . . FIXME
many more
dgTMatrix general, numeric, sparse matrices in (a possibly redundant) triplet form. This can be a conve- — maybe ex
nient form in which to construct sparse matrices. plain naming
dgCMatrix general, numeric, sparse matrices in the (sorted) compressed sparse column format. scheme? . . .
dsCMatrix symmetric, real, sparse matrices in the (sorted) compressed sparse column format. Only the
upper or the lower triangle is stored. Although there is provision for both forms, the lower triangle
form works best with TAUCS.
dtCMatrix triangular, real, sparse matrices in the (sorted) compressed sparse column format.
Todo: Can also read and write the Matrix Market and read the Harwell-Boeing representations.
Todo: Can convert from a dense matrix to a sparse matrix (or use the Matrix function) but going through
an intermediate dense matrix may cause problems with the amount of memory required.
Todo: similar range of operations as for the dense matrix classes.
5 Session Info
> toLatex(sessionInfo())
8
• Base packages: base, datasets, grDevices, graphics, methods, stats, utils
• Other packages: Matrix 1.2-18
• Loaded via a namespace (and not attached): compiler 3.6.1, grid 3.6.1, lattice 0.20-38, tools 3.6.1
References
E. Anderson, Z. Bai, C. Bischof, S. Blackford, J. Demmel, J. Dongarra, J. Du Croz, A. Greenbaum, S. Ham-
marling, A. McKenney, and D. Sorensen. LAPACK Users’ Guide. SIAM, Philadelphia, PA, 3rd edition,
1999.
Tim Davis. CHOLMOD: sparse supernodal Cholesky factorization and update/downdate.
http://www.cise.ufl.edu/research/sparse/cholmod, 2005a.