1 |
#### Toplevel ``virtual'' class "Matrix" |
#### Toplevel ``virtual'' class "Matrix" |
2 |
|
|
|
## probably not needed eventually: |
|
|
setAs(from = "ddenseMatrix", to = "matrix", |
|
|
function(from) { |
|
|
if(length(d <- dim(from)) != 2) stop("dim(.) has not length 2") |
|
|
array(from@x, dim = d, dimnames = dimnames(from)) |
|
|
}) |
|
3 |
|
|
4 |
## private function to be used as show() method possibly more than once |
### Virtual coercions -- via smart "helpers" (-> ./Auxiliaries.R) |
|
prMatrix <- function(object) { |
|
|
d <- dim(object) |
|
|
cl <- class(object) |
|
|
cat(sprintf('%d x %d Matrix of class "%s"\n', d[1], d[2], cl)) |
|
|
##- no longer needed: have no objects of virtual classes: |
|
|
## if(cl == "Matrix") { ## have no data slot |
|
|
## cat("Dim = ", d) |
|
|
## if(any(sapply(object@Dimnames,length) > 0)) { |
|
|
## cat("; Dimnames = ") |
|
|
## str(object@Dimnames) |
|
|
## } |
|
|
## cat("\n") |
|
|
## } else { # not "Matrix", hence have data 'x' slot |
|
|
m <- as(object, "matrix") |
|
|
maxp <- getOption("max.print") |
|
|
if(prod(d) <= maxp) print(m) |
|
|
else { ## d[1] > maxp / d[2] >= nr : |
|
|
nr <- maxp %/% d[2] |
|
|
n2 <- ceiling(nr / 2) |
|
|
print(head(m, max(1, n2))) |
|
|
cat("\n ..........\n\n") |
|
|
print(tail(m, max(1, nr - n2))) |
|
|
} |
|
|
## DEBUG: cat("str(.):\n") ; str(object) |
|
|
## } |
|
|
invisible(object)# as print() S3 methods do |
|
|
} |
|
|
|
|
|
setMethod("show", signature(object = "ddenseMatrix"), prMatrix) |
|
|
|
|
|
setMethod("show", signature(object = "sparseMatrix"), |
|
|
function(object) { |
|
|
d <- dim(object) |
|
|
cl <- class(object) |
|
|
cat(sprintf('%d x %d sparse Matrix of class "%s"\n', d[1], d[2], cl)) |
|
|
|
|
|
maxp <- getOption("max.print") |
|
|
if(prod(d) <= maxp) print(as(object, "matrix")) |
|
|
else { ## d[1] > maxp / d[2] >= nr : |
|
|
cat("\n Not printing large sparse matrix -- maybe increase options(max.print)\n") |
|
|
if(FALSE) { ### need storage economic "[,]" method for sparse!! |
|
|
nr <- maxp %/% d[2] |
|
|
n2 <- ceiling(nr / 2) |
|
|
print(head(m, max(1, n2))) |
|
|
cat("\n ..........\n\n") |
|
|
print(tail(m, max(1, nr - n2))) |
|
|
} |
|
|
} |
|
|
## DEBUG: cat("str(.):\n") ; str(object) |
|
|
invisible(object) |
|
|
}) |
|
5 |
|
|
6 |
## this may go away {since sparse matrices need something better!} : |
setAs("Matrix", "sparseMatrix", function(from) as(from, "CsparseMatrix")) |
7 |
setMethod("show", signature(object = "Matrix"), prMatrix) |
setAs("Matrix", "CsparseMatrix", function(from) as_Csparse(from)) |
8 |
|
setAs("Matrix", "denseMatrix", function(from) as_dense(from)) |
9 |
|
|
10 |
|
## Maybe TODO: |
11 |
|
## setAs("Matrix", "nMatrix", function(from) ....) |
12 |
|
|
13 |
|
## Most of these work; this is a last resort: |
14 |
|
setAs(from = "Matrix", to = "matrix", # do *not* call base::as.matrix() here: |
15 |
|
function(from) .bail.out.2("coerce", class(from), class(to))) |
16 |
|
setAs(from = "matrix", to = "Matrix", function(from) Matrix(from)) |
17 |
|
|
18 |
|
## ## probably not needed eventually: |
19 |
|
## setAs(from = "ddenseMatrix", to = "matrix", |
20 |
|
## function(from) { |
21 |
|
## if(length(d <- dim(from)) != 2) stop("dim(.) has not length 2") |
22 |
|
## array(from@x, dim = d, dimnames = dimnames(from)) |
23 |
|
## }) |
24 |
|
|
25 |
## should propagate to all subclasses: |
## should propagate to all subclasses: |
26 |
setMethod("as.matrix", signature(x = "Matrix"), function(x) as(x, "matrix")) |
setMethod("as.matrix", signature(x = "Matrix"), function(x) as(x, "matrix")) |
27 |
|
## for 'Matrix' objects, as.array() should be equivalent: |
28 |
|
setMethod("as.array", signature(x = "Matrix"), function(x) as(x, "matrix")) |
29 |
|
|
30 |
|
## head and tail apply to all Matrix objects for which subscripting is allowed: |
31 |
|
setMethod("head", signature(x = "Matrix"), utils::head.matrix) |
32 |
|
setMethod("tail", signature(x = "Matrix"), utils::tail.matrix) |
33 |
|
|
34 |
|
setMethod("drop", signature(x = "Matrix"), |
35 |
|
function(x) if(all(dim(x) != 1)) x else drop(as(x, "matrix"))) |
36 |
|
|
37 |
|
## slow "fall back" method {subclasses should have faster ones}: |
38 |
|
setMethod("as.vector", signature(x = "Matrix", mode = "missing"), |
39 |
|
function(x) as.vector(as(x, "matrix"))) |
40 |
|
|
41 |
|
## mainly need these for "dMatrix" or "lMatrix" respectively, but why not general: |
42 |
|
setMethod("as.numeric", signature(x = "Matrix"), |
43 |
|
function(x, ...) as.numeric(as.vector(x))) |
44 |
|
setMethod("as.logical", signature(x = "Matrix"), |
45 |
|
function(x, ...) as.logical(as.vector(x))) |
46 |
|
|
47 |
|
setMethod("cov2cor", signature(V = "Matrix"), |
48 |
|
function(V) as(cov2cor(as(V, "matrix")), "dpoMatrix")) |
49 |
|
|
50 |
|
## "base" has an isSymmetric() S3-generic since R 2.3.0 |
51 |
|
setMethod("isSymmetric", signature(object = "symmetricMatrix"), |
52 |
|
function(object,tol) TRUE) |
53 |
|
setMethod("isSymmetric", signature(object = "triangularMatrix"), |
54 |
|
## TRUE iff diagonal: |
55 |
|
function(object,tol) isDiagonal(object)) |
56 |
|
|
57 |
|
setMethod("isTriangular", signature(object = "triangularMatrix"), |
58 |
|
function(object, ...) TRUE) |
59 |
|
|
60 |
|
setMethod("isTriangular", signature(object = "matrix"), isTriMat) |
61 |
|
|
62 |
|
setMethod("isDiagonal", signature(object = "matrix"), .is.diagonal) |
63 |
|
|
64 |
|
|
65 |
|
|
66 |
setMethod("dim", signature(x = "Matrix"), |
setMethod("dim", signature(x = "Matrix"), |
67 |
function(x) x@Dim, valueClass = "integer") |
function(x) x@Dim, valueClass = "integer") |
68 |
|
|
69 |
|
setMethod("length", "Matrix", function(x) prod(dim(x))) |
70 |
|
|
71 |
setMethod("dimnames", signature(x = "Matrix"), function(x) x@Dimnames) |
setMethod("dimnames", signature(x = "Matrix"), function(x) x@Dimnames) |
72 |
|
|
73 |
|
|
74 |
## not exported but used more than once for "dimnames<-" method : |
## not exported but used more than once for "dimnames<-" method : |
75 |
## -- or do only once for all "Matrix" classes ?? |
## -- or do only once for all "Matrix" classes ?? |
76 |
dimnamesGets <- function (x, value) { |
dimnamesGets <- function (x, value) { |
89 |
setMethod("unname", signature("Matrix", force="missing"), |
setMethod("unname", signature("Matrix", force="missing"), |
90 |
function(obj) { obj@Dimnames <- list(NULL,NULL); obj}) |
function(obj) { obj@Dimnames <- list(NULL,NULL); obj}) |
91 |
|
|
92 |
|
setMethod("all", signature(x = "Matrix"), |
93 |
|
function(x, ..., na.rm) |
94 |
|
callGeneric(as(x, "lMatrix"), ..., na.rm=na.rm)) |
95 |
|
|
96 |
|
setMethod("any", signature(x = "Matrix"), |
97 |
|
function(x, ..., na.rm) |
98 |
|
callGeneric(as(x, "lMatrix"), ..., na.rm=na.rm)) |
99 |
|
|
100 |
|
## NOTE: "&" and "|" are now in group "Logic" c "Ops" --> ./Ops.R |
101 |
|
## "!" is in ./not.R |
102 |
|
|
103 |
|
|
104 |
Matrix <- |
Matrix <- |
105 |
function (data = NA, nrow = 1, ncol = 1, byrow = FALSE, dimnames = NULL) |
function (data = NA, nrow = 1, ncol = 1, byrow = FALSE, dimnames = NULL, |
106 |
|
sparse = NULL, forceCheck = FALSE) |
107 |
{ |
{ |
108 |
if (is(data, "Matrix")) return(data) |
sparseDefault <- function(m) prod(dim(m)) > 2*sum(isN0(as(m, "matrix"))) |
109 |
if (is.matrix(data)) { val <- data } |
|
110 |
else { ## cut & paste from "base::matrix" : |
i.M <- is(data, "Matrix") |
111 |
|
if(!i.M && inherits(data, "table")) # special treatment |
112 |
|
class(data) <- "matrix" # "matrix" first for S4 dispatch |
113 |
|
if(is.null(sparse1 <- sparse) && (i.M || is(data, "matrix"))) |
114 |
|
sparse <- sparseDefault(data) |
115 |
|
|
116 |
|
doDN <- TRUE |
117 |
|
if (i.M) { |
118 |
|
if(!missing(nrow) || !missing(ncol)|| !missing(byrow)) |
119 |
|
warning("'nrow', 'ncol', etc, are disregarded when 'data' is \"Matrix\" already") |
120 |
|
sM <- is(data,"sparseMatrix") |
121 |
|
if(!forceCheck && ((sparse && sM) || (!sparse && !sM))) |
122 |
|
return(data) |
123 |
|
## else : convert dense <-> sparse -> at end |
124 |
|
} |
125 |
|
else if (!is.matrix(data)) { ## cut & paste from "base::matrix" : |
126 |
if (missing(nrow)) |
if (missing(nrow)) |
127 |
nrow <- ceiling(length(data)/ncol) |
nrow <- ceiling(length(data)/ncol) |
128 |
else if (missing(ncol)) |
else if (missing(ncol)) |
129 |
ncol <- ceiling(length(data)/nrow) |
ncol <- ceiling(length(data)/nrow) |
130 |
val <- .Internal(matrix(data, nrow, ncol, byrow)) |
if(length(data) == 1 && is0(data) && !identical(sparse, FALSE)) { |
131 |
dimnames(val) <- dimnames |
## Matrix(0, ...) : always sparse unless "sparse = FALSE": |
132 |
} |
if(is.null(sparse)) sparse1 <- sparse <- TRUE |
133 |
as(val, "dgeMatrix") |
i.M <- sM <- TRUE |
134 |
} |
## will be sparse: do NOT construct full matrix! |
135 |
|
data <- new(if(is.numeric(data)) "dgTMatrix" else |
136 |
|
if(is.logical(data)) "lgTMatrix" else |
137 |
|
stop("invalid 'data'"), |
138 |
|
Dim = as.integer(c(nrow,ncol)), |
139 |
|
Dimnames = if(is.null(dimnames)) list(NULL,NULL) |
140 |
|
else dimnames) |
141 |
|
} else { ## normal case - using .Internal() to avoid more copying |
142 |
|
if(getRversion() >= "2.7.0") |
143 |
|
data <- .Internal(matrix(data, nrow, ncol, byrow, dimnames)) |
144 |
|
else { |
145 |
|
data <- .Internal(matrix(data, nrow, ncol, byrow)) |
146 |
|
dimnames(data) <- dimnames |
147 |
|
} |
148 |
|
if(is.null(sparse)) |
149 |
|
sparse <- sparseDefault(data) |
150 |
|
} |
151 |
|
doDN <- FALSE |
152 |
|
} else if(!missing(nrow) || !missing(ncol)|| !missing(byrow)) |
153 |
|
warning("'nrow', 'ncol', etc, are disregarded for matrix 'data'") |
154 |
|
|
155 |
|
## 'data' is now a "matrix" or "Matrix" |
156 |
|
if (doDN && !is.null(dimnames)) |
157 |
|
dimnames(data) <- dimnames |
158 |
|
|
159 |
|
## check for symmetric / triangular / diagonal : |
160 |
|
isSym <- isSymmetric(data) |
161 |
|
if((isTri <- !isSym)) |
162 |
|
isTri <- isTriangular(data) |
163 |
|
isDiag <- isSym # cannot be diagonal if it isn't symmetric |
164 |
|
if(isDiag) |
165 |
|
isDiag <- isDiagonal(data) |
166 |
|
|
167 |
|
## Find proper matrix class 'cl' |
168 |
|
cl <- |
169 |
|
if(isDiag && !isTRUE(sparse1)) |
170 |
|
"diagonalMatrix" # -> will automatically check for type |
171 |
|
else { |
172 |
|
## consider it's type |
173 |
|
ctype <- |
174 |
|
if(is(data,"Matrix")) class(data) |
175 |
|
else { |
176 |
|
if("complex" == (ctype <- typeof(data))) |
177 |
|
"z" else ctype |
178 |
|
} |
179 |
|
ctype <- substr(ctype, 1,1) # "d", "l", "i" or "z" |
180 |
|
if(ctype == "z") |
181 |
|
stop("complex matrices not yet implemented in Matrix package") |
182 |
|
if(ctype == "i") { |
183 |
|
warning("integer matrices not yet implemented in 'Matrix'; ", |
184 |
|
"using 'double' ones'") |
185 |
|
ctype <- "d" |
186 |
|
} |
187 |
|
paste(ctype, |
188 |
|
if(sparse) { |
189 |
|
if(isSym) "sCMatrix" else |
190 |
|
if(isTri) "tCMatrix" else "gCMatrix" |
191 |
|
} else { ## dense |
192 |
|
if(isSym) "syMatrix" else |
193 |
|
if(isTri) "trMatrix" else "geMatrix" |
194 |
|
}, sep="") |
195 |
|
} |
196 |
|
|
197 |
|
## Can we coerce and be done? |
198 |
|
if(!canCoerce(data,cl)) { ## try to coerce ``via'' virtual classes |
199 |
|
if(sparse && !sM) |
200 |
|
data <- as(data, "sparseMatrix") |
201 |
|
else if(!sparse && !is(data, "denseMatrix")) |
202 |
|
data <- as(data, "denseMatrix") |
203 |
|
if(isTri && !is(data, "triangularMatrix")) |
204 |
|
data <- as(data, "triangularMatrix") |
205 |
|
else if(isSym && !is(data, "symmetricMatrix")) |
206 |
|
data <- as(data, "symmetricMatrix") |
207 |
|
} |
208 |
|
## now coerce in any case .. maybe producing sensible error message: |
209 |
|
as(data, cl) |
210 |
|
} |
211 |
|
|
212 |
|
## Methods for operations where one argument is numeric |
213 |
|
|
214 |
|
## Using as.matrix() and rbind() |
215 |
|
## in order to get dimnames from names {at least potentially}: |
216 |
|
|
217 |
|
setMethod("%*%", signature(x = "Matrix", y = "numeric"), |
218 |
|
function(x, y) callGeneric(x, as.matrix(y))) |
219 |
|
setMethod("%*%", signature(x = "numeric", y = "Matrix"), |
220 |
|
function(x, y) callGeneric(matrix(x, nrow = 1, byrow=TRUE), y)) |
221 |
|
|
222 |
|
setMethod("%*%", signature(x = "Matrix", y = "matrix"), |
223 |
|
function(x, y) callGeneric(x, Matrix(y))) |
224 |
|
setMethod("%*%", signature(x = "matrix", y = "Matrix"), |
225 |
|
function(x, y) callGeneric(Matrix(x), y)) |
226 |
|
|
227 |
|
|
228 |
|
setMethod("crossprod", signature(x = "Matrix", y = "numeric"), |
229 |
|
function(x, y = NULL) callGeneric(x, as.matrix(y))) |
230 |
|
setMethod("crossprod", signature(x = "numeric", y = "Matrix"), |
231 |
|
function(x, y = NULL) callGeneric(as.matrix(x), y)) |
232 |
|
|
233 |
|
setMethod("crossprod", signature(x = "Matrix", y = "matrix"), |
234 |
|
function(x, y = NULL) callGeneric(x, Matrix(y))) |
235 |
|
setMethod("crossprod", signature(x = "matrix", y = "Matrix"), |
236 |
|
function(x, y = NULL) callGeneric(Matrix(x), y)) |
237 |
|
|
238 |
|
## The as.matrix() promotion seems illogical to MM, |
239 |
|
## but is according to help(tcrossprod, package = "base") : |
240 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "numeric"), |
241 |
|
function(x, y = NULL) callGeneric(x, as.matrix(y))) |
242 |
|
setMethod("tcrossprod", signature(x = "numeric", y = "Matrix"), |
243 |
|
function(x, y = NULL) callGeneric(as.matrix(x), y)) |
244 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "matrix"), |
245 |
|
function(x, y = NULL) callGeneric(x, Matrix(y))) |
246 |
|
setMethod("tcrossprod", signature(x = "matrix", y = "Matrix"), |
247 |
|
function(x, y = NULL) callGeneric(Matrix(x), y)) |
248 |
|
|
249 |
|
## maybe not 100% optimal, but elegant: |
250 |
|
setMethod("solve", signature(a = "Matrix", b = "missing"), |
251 |
|
function(a, b, ...) solve(a, Diagonal(nrow(a)))) |
252 |
|
|
253 |
|
setMethod("solve", signature(a = "Matrix", b = "numeric"), |
254 |
|
function(a, b, ...) callGeneric(a, Matrix(b))) |
255 |
|
setMethod("solve", signature(a = "Matrix", b = "matrix"), |
256 |
|
function(a, b, ...) callGeneric(a, Matrix(b))) |
257 |
|
setMethod("solve", signature(a = "matrix", b = "Matrix"), |
258 |
|
function(a, b, ...) callGeneric(Matrix(a), b)) |
259 |
|
|
260 |
|
## when no sub-class method is found, bail out |
261 |
|
setMethod("solve", signature(a = "Matrix", b = "Matrix"), |
262 |
|
function(a, b, ...) .bail.out.2("solve", class(a), class(b))) |
263 |
|
|
264 |
|
## bail-out methods in order to get better error messages |
265 |
|
setMethod("%*%", signature(x = "Matrix", y = "Matrix"), |
266 |
|
function (x, y) |
267 |
|
stop(gettextf('not-yet-implemented method for <%s> %%*%% <%s>', |
268 |
|
class(x), class(y)))) |
269 |
|
|
270 |
|
setMethod("crossprod", signature(x = "Matrix", y = "ANY"), |
271 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
272 |
|
setMethod("crossprod", signature(x = "ANY", y = "Matrix"), |
273 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
274 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "ANY"), |
275 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
276 |
|
setMethod("tcrossprod", signature(x = "ANY", y = "Matrix"), |
277 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
278 |
|
|
279 |
|
## cheap fallbacks |
280 |
|
setMethod("crossprod", signature(x = "Matrix", y = "Matrix"), |
281 |
|
function(x, y = NULL) t(x) %*% y) |
282 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "Matrix"), |
283 |
|
function(x, y = NULL) x %*% t(y)) |
284 |
|
|
285 |
|
## There are special sparse methods; this is a "fall back": |
286 |
|
setMethod("kronecker", signature(X = "Matrix", Y = "ANY", |
287 |
|
FUN = "ANY", make.dimnames = "ANY"), |
288 |
|
function(X, Y, FUN, make.dimnames, ...) { |
289 |
|
if(is(X, "sparseMatrix")) |
290 |
|
warning("using slow kronecker() method") |
291 |
|
X <- as(X, "matrix") ; Matrix(callGeneric()) }) |
292 |
|
|
293 |
|
setMethod("kronecker", signature(X = "ANY", Y = "Matrix", |
294 |
|
FUN = "ANY", make.dimnames = "ANY"), |
295 |
|
function(X, Y, FUN, make.dimnames, ...) { |
296 |
|
if(is(Y, "sparseMatrix")) |
297 |
|
warning("using slow kronecker() method") |
298 |
|
Y <- as(Y, "matrix") ; Matrix(callGeneric()) }) |
299 |
|
|
300 |
|
|
301 |
|
## FIXME: All of these should never be called |
302 |
|
setMethod("chol", signature(x = "Matrix"), |
303 |
|
function(x, pivot = FALSE) .bail.out.1(.Generic, class(x))) |
304 |
|
setMethod("determinant", signature(x = "Matrix"), |
305 |
|
function(x, logarithm = TRUE) .bail.out.1(.Generic, class(x))) |
306 |
|
|
307 |
|
setMethod("diag", signature(x = "Matrix"), |
308 |
|
function(x, nrow, ncol) .bail.out.1(.Generic, class(x))) |
309 |
|
setMethod("t", signature(x = "Matrix"), |
310 |
|
function(x) .bail.out.1(.Generic, class(x))) |
311 |
|
|
312 |
|
setMethod("norm", signature(x = "Matrix", type = "character"), |
313 |
|
function(x, type, ...) .bail.out.1(.Generic, class(x))) |
314 |
|
setMethod("rcond", signature(x = "Matrix", type = "character"), |
315 |
|
function(x, type, ...) .bail.out.1(.Generic, class(x))) |
316 |
|
|
317 |
|
|
318 |
|
## for all : |
319 |
|
setMethod("norm", signature(x = "ANY", type = "missing"), |
320 |
|
function(x, type, ...) norm(x, type = "O", ...)) |
321 |
|
setMethod("rcond", signature(x = "ANY", type = "missing"), |
322 |
|
function(x, type, ...) rcond(x, type = "O", ...)) |
323 |
|
|
324 |
|
|
|
if(FALSE) { ##--- not-yet used -- {almost same code also in ./dgeMatrix.R } |
|
325 |
|
|
326 |
## utility for as.Matrix() {which is currently invalid } |
|
327 |
Matrix.class <- function(x, tol = 0, symmetry = TRUE, unit.diagonal = TRUE, |
|
328 |
triangularity = c(TRUE, TRUE), |
## MM: More or less "Cut & paste" from |
329 |
orthogonality = c(TRUE, TRUE), |
## --- diff.default() from R/src/library/base/R/diff.R : |
330 |
normality = c(TRUE, TRUE)) |
setMethod("diff", signature(x = "Matrix"), |
331 |
{ |
function(x, lag = 1, differences = 1, ...) { |
332 |
val <- "Matrix" |
if (length(lag) > 1 || length(differences) > 1 || |
333 |
x <- as.matrix(x) |
lag < 1 || differences < 1) |
334 |
if (symmetry) { |
stop("'lag' and 'differences' must be integers >= 1") |
335 |
if (is.Hermitian(x, tol)) val <- c("Hermitian", val) |
xlen <- nrow(x) |
336 |
} |
if (lag * differences >= xlen) |
337 |
if (triangularity[1]) { |
return(x[,FALSE][0]) # empty of proper mode |
338 |
if (is.LowerTriangular(x, tol)) { |
|
339 |
val <- c("LowerTriangular", val) |
i1 <- -1:-lag |
340 |
if (unit.diagonal) |
for (i in 1:differences) |
341 |
if (max(Mod(diag(x) - 1)) <= tol) |
x <- x[i1, , drop = FALSE] - |
342 |
val <- c("UnitLowerTriangular", val) |
x[-nrow(x):-(nrow(x)-lag+1), , drop = FALSE] |
343 |
} |
x |
344 |
} |
}) |
345 |
if (triangularity[2]) { |
|
346 |
if (is.UpperTriangular(x, tol)) { |
setMethod("image", "Matrix", |
347 |
val <- c("UpperTriangular", val) |
function(x, ...) { # coercing to sparse is not inefficient, |
348 |
if (unit.diagonal) |
## since we need 'i' and 'j' for levelplot() |
349 |
if (max(Mod(diag(x) - 1)) <= tol) |
x <- as(as(x, "sparseMatrix"), "dMatrix") |
350 |
val <- c("UnitUpperTriangular", val) |
callGeneric() |
351 |
} |
}) |
352 |
} |
|
353 |
if (orthogonality[1]) { |
|
354 |
if (is.ColOrthonormal(x, tol)) { |
## Group Methods |
355 |
val <- c("ColOrthoNormal", "ColOrthogonal", val) |
|
356 |
} else { |
##-> see ./Ops.R |
357 |
if (Orthogonal.test(x, normal = FALSE) <= tol) |
## ~~~~~ |
358 |
val <- c("ColOrthogonal", val) |
## For all non-dMatrix objects, and note that "all" and "any" have their own |
359 |
} |
setMethod("Summary", signature(x = "Matrix", na.rm = "ANY"), |
360 |
} |
function(x, ..., na.rm) |
361 |
if (orthogonality[2]) { |
callGeneric(as(x,"dMatrix"), ..., na.rm = na.rm)) |
362 |
if (normality[2] && is.RowOrthonormal(x, tol)) { |
|
363 |
val <- c("RowOrthoNormal", "RowOrthogonal", val) |
|
364 |
|
### -------------------------------------------------------------------------- |
365 |
|
### |
366 |
|
### Subsetting "[" and |
367 |
|
### SubAssign "[<-" : The "missing" cases can be dealt with here, "at the top": |
368 |
|
|
369 |
|
## Using "index" for indices should allow |
370 |
|
## integer (numeric), logical, or character (names!) indices : |
371 |
|
|
372 |
|
## "x[]": |
373 |
|
setMethod("[", signature(x = "Matrix", |
374 |
|
i = "missing", j = "missing", drop = "ANY"), |
375 |
|
function (x, i, j, ..., drop) x) |
376 |
|
|
377 |
|
## missing 'drop' --> 'drop = TRUE' |
378 |
|
## ----------- |
379 |
|
## select rows |
380 |
|
setMethod("[", signature(x = "Matrix", i = "index", j = "missing", |
381 |
|
drop = "missing"), |
382 |
|
function(x,i,j, ..., drop) { |
383 |
|
if(nargs() == 2) { ## e.g. M[0] , M[TRUE], M[1:2] |
384 |
|
if(any(i) || prod(dim(x)) == 0) |
385 |
|
as.vector(x)[i] |
386 |
|
else ## save memory |
387 |
|
as.vector(x[1,1])[FALSE] |
388 |
} else { |
} else { |
389 |
if (Orthogonal.test(x, byrow = TRUE, normal = FALSE) <= tol) |
callGeneric(x, i=i, , drop=TRUE) |
390 |
val <- c("RowOrthogonal", val) |
## ^^ |
|
} |
|
|
} |
|
|
val |
|
391 |
} |
} |
392 |
|
}) |
393 |
|
|
394 |
|
## select columns |
395 |
|
setMethod("[", signature(x = "Matrix", i = "missing", j = "index", |
396 |
|
drop = "missing"), |
397 |
|
function(x,i,j, ..., drop) callGeneric(x, j=j, drop= TRUE)) |
398 |
|
setMethod("[", signature(x = "Matrix", i = "index", j = "index", |
399 |
|
drop = "missing"), |
400 |
|
function(x,i,j, ..., drop) callGeneric(x, i=i, j=j, drop= TRUE)) |
401 |
|
|
402 |
|
## bail out if any of (i,j,drop) is "non-sense" |
403 |
|
setMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", drop = "ANY"), |
404 |
|
function(x,i,j, ..., drop) |
405 |
|
stop("invalid or not-yet-implemented 'Matrix' subsetting")) |
406 |
|
|
407 |
|
## logical indexing, such as M[ M >= 7 ] *BUT* also M[ M[,1] >= 3,], |
408 |
|
## The following is *both* for M [ <logical> ] |
409 |
|
## and also for M [ <logical> , ] |
410 |
|
.M.sub.i.logical <- function (x, i, j, ..., drop) |
411 |
|
{ |
412 |
|
nA <- nargs() |
413 |
|
if(nA == 2) { ## M [ M >= 7 ] |
414 |
|
## FIXME: when both 'x' and 'i' are sparse, this can be very inefficient |
415 |
|
as(x, geClass(x))@x[as.vector(i)] |
416 |
|
## -> error when lengths don't match |
417 |
|
} else if(nA == 3) { ## M [ M[,1, drop=FALSE] >= 7, ] |
418 |
|
stop("not-yet-implemented 'Matrix' subsetting") ## FIXME |
419 |
|
|
420 |
|
} else stop("nargs() = ", nA, |
421 |
|
". Extraneous illegal arguments inside '[ .. ]' (i.logical)?") |
422 |
|
} |
423 |
|
setMethod("[", signature(x = "Matrix", i = "lMatrix", j = "missing", |
424 |
|
drop = "ANY"), |
425 |
|
.M.sub.i.logical) |
426 |
|
setMethod("[", signature(x = "Matrix", i = "logical", j = "missing", |
427 |
|
drop = "ANY"), |
428 |
|
.M.sub.i.logical) |
429 |
|
|
430 |
as.Matrix <- function(x, tol = .Machine$double.eps) |
|
431 |
|
## A[ ij ] where ij is (i,j) 2-column matrix -- but also when that is logical mat! |
432 |
|
.M.sub.i.2col <- function (x, i, j, ..., drop) |
433 |
{ |
{ |
434 |
asObject(if (inherits(x, "Matrix")) x else as.matrix(x), |
nA <- nargs() |
435 |
Matrix.class(x, tol = tol)) |
if(nA == 2) { ## M [ cbind(ii,jj) ] or M [ <logical matrix> ] |
436 |
|
if(!is.integer(nc <- ncol(i))) |
437 |
|
stop(".M.sub.i.2col(): 'i' has no integer column number;\n", |
438 |
|
"should never happen; please report") |
439 |
|
if(is.logical(i)) |
440 |
|
return(.M.sub.i.logical(x, i=i)) # call with 2 args! |
441 |
|
else if(!is.numeric(i) || nc != 2) |
442 |
|
stop("such indexing must be by logical or 2-column numeric matrix") |
443 |
|
m <- nrow(i) |
444 |
|
if(m == 0) return(vector(mode = .type.kind[.M.kind(x)])) |
445 |
|
## else |
446 |
|
i1 <- i[,1] |
447 |
|
i2 <- i[,2] |
448 |
|
## potentially inefficient -- FIXME -- |
449 |
|
unlist(lapply(seq_len(m), function(j) x[i1[j], i2[j]])) |
450 |
|
|
451 |
|
} else stop("nargs() = ", nA, |
452 |
|
". Extraneous illegal arguments inside '[ .. ]' (i.2col)?") |
453 |
|
} |
454 |
|
setMethod("[", signature(x = "Matrix", i = "matrix", j = "missing"),# drop="ANY" |
455 |
|
.M.sub.i.2col) |
456 |
|
|
457 |
|
|
458 |
|
### "[<-" : ----------------- |
459 |
|
|
460 |
|
## x[] <- value : |
461 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "missing", j = "missing", |
462 |
|
value = "ANY"),## double/logical/... |
463 |
|
function (x, value) { |
464 |
|
## Fails for 'nMatrix' ... FIXME : make sure have method there |
465 |
|
x@x <- rep(value, length = length(x@x)) |
466 |
|
validObject(x)# check if type and lengths above match |
467 |
|
x |
468 |
|
}) |
469 |
|
|
470 |
|
## A[ ij ] <- value, where ij is (i,j) 2-column matrix : |
471 |
|
## ---------------- |
472 |
|
## The cheap general method --- FIXME: provide special ones; done for Tsparse.. |
473 |
|
## NOTE: need '...' below such that setMethod() does |
474 |
|
## not use .local() such that nargs() will work correctly: |
475 |
|
.M.repl.i.2col <- function (x, i, j, ..., value) |
476 |
|
{ |
477 |
|
nA <- nargs() |
478 |
|
if(nA == 3) { ## M [ cbind(ii,jj) ] <- value or M [ Lmat ] <- value |
479 |
|
if(!is.integer(nc <- ncol(i))) |
480 |
|
stop(".M.repl.i.2col(): 'i' has no integer column number;\n", |
481 |
|
"should never happen; please report") |
482 |
|
else if(!is.numeric(i) || nc != 2) |
483 |
|
stop("such indexing must be by logical or 2-column numeric matrix") |
484 |
|
if(is.logical(i)) { |
485 |
|
message(".M.repl.i.2col(): drop 'matrix' case ...") |
486 |
|
## c(i) : drop "matrix" to logical vector |
487 |
|
return( callGeneric(x, i=c(i), value=value) ) |
488 |
|
} |
489 |
|
if(!is.integer(i)) storage.mode(i) <- "integer" |
490 |
|
if(any(i < 0)) |
491 |
|
stop("negative values are not allowed in a matrix subscript") |
492 |
|
if(any(is.na(i))) |
493 |
|
stop("NAs are not allowed in subscripted assignments") |
494 |
|
if(any(i0 <- (i == 0))) # remove them |
495 |
|
i <- i[ - which(i0, arr.ind = TRUE)[,"row"], ] |
496 |
|
## now have integer i >= 1 |
497 |
|
m <- nrow(i) |
498 |
|
## mod.x <- .type.kind[.M.kind(x)] |
499 |
|
if(length(value) > 0 && m %% length(value) != 0) |
500 |
|
warning("number of items to replace is not a multiple of replacement length") |
501 |
|
## recycle: |
502 |
|
value <- rep(value, length = m) |
503 |
|
i1 <- i[,1] |
504 |
|
i2 <- i[,2] |
505 |
|
## inefficient -- FIXME -- (also loses "symmetry" unnecessarily) |
506 |
|
for(k in seq_len(m)) |
507 |
|
x[i1[k], i2[k]] <- value[k] |
508 |
|
|
509 |
|
x |
510 |
|
} else stop("nargs() = ", nA, |
511 |
|
". Extraneous illegal arguments inside '[ .. ]' ?") |
512 |
} |
} |
513 |
|
|
514 |
}## not-yet used |
setReplaceMethod("[", signature(x = "Matrix", i = "matrix", j = "missing", |
515 |
|
value = "replValue"), |
516 |
|
.M.repl.i.2col) |
517 |
|
|
518 |
|
|
519 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "missing", j = "ANY", |
520 |
|
value = "Matrix"), |
521 |
|
function (x, i, j, ..., value) |
522 |
|
callGeneric(x=x, , j=j, value = as.vector(value))) |
523 |
|
|
524 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "missing", |
525 |
|
value = "Matrix"), |
526 |
|
function (x, i, j, ..., value) |
527 |
|
callGeneric(x=x, i=i, , value = as.vector(value))) |
528 |
|
|
529 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", |
530 |
|
value = "Matrix"), |
531 |
|
function (x, i, j, ..., value) |
532 |
|
callGeneric(x=x, i=i, j=j, value = as.vector(value))) |
533 |
|
|
534 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "missing", j = "ANY", |
535 |
|
value = "matrix"), |
536 |
|
function (x, i, j, ..., value) |
537 |
|
callGeneric(x=x, , j=j, value = c(value))) |
538 |
|
|
539 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "missing", |
540 |
|
value = "matrix"), |
541 |
|
function (x, i, j, ..., value) |
542 |
|
callGeneric(x=x, i=i, , value = c(value))) |
543 |
|
|
544 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", |
545 |
|
value = "matrix"), |
546 |
|
function (x, i, j, value) |
547 |
|
callGeneric(x=x, i=i, j=j, value = c(value))) |
548 |
|
|
549 |
|
## (ANY,ANY,ANY) is used when no `real method' is implemented : |
550 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", |
551 |
|
value = "ANY"), |
552 |
|
function (x, i, j, value) { |
553 |
|
if(!is.atomic(value)) |
554 |
|
stop(sprintf("RHS 'value' (class %s) matches 'ANY', but must match matrix class %s", |
555 |
|
class(value),class(x))) |
556 |
|
else stop("not-yet-implemented 'Matrix[<-' method") |
557 |
|
}) |