1 |
### Define Methods that can be inherited for all subclasses |
### Define Methods that can be inherited for all subclasses |
2 |
|
|
3 |
|
## This replaces many "d..Matrix" -> "dgeMatrix" ones |
4 |
|
## >> but << needs all sub(sub(sub)) classes of "ddenseMatrix" listed |
5 |
|
## ----- in ../src/Mutils.c |
6 |
|
|
7 |
|
## Should this method return 'from' without duplication when it has |
8 |
|
## class dgeMatrix? |
9 |
|
setAs("ddenseMatrix", "dgeMatrix", |
10 |
|
function(from) { |
11 |
|
if (class(from) != "dgeMatrix") |
12 |
|
from <- .Call(dup_mMatrix_as_dgeMatrix, from) |
13 |
|
from |
14 |
|
}) |
15 |
|
|
16 |
|
## d(ouble) to l(ogical): |
17 |
|
setAs("dgeMatrix", "lgeMatrix", d2l_Matrix) |
18 |
|
setAs("dtrMatrix", "ltrMatrix", d2l_Matrix) |
19 |
|
setAs("dtpMatrix", "ltpMatrix", d2l_Matrix) |
20 |
|
setAs("dsyMatrix", "lsyMatrix", d2l_Matrix) |
21 |
|
setAs("dspMatrix", "lspMatrix", d2l_Matrix) |
22 |
|
|
23 |
|
setAs("ddenseMatrix", "CsparseMatrix", |
24 |
|
function(from) { |
25 |
|
if (class(from) != "dgeMatrix") |
26 |
|
from <- .Call(dup_mMatrix_as_dgeMatrix, from) |
27 |
|
.Call(dense_to_Csparse, from) |
28 |
|
}) |
29 |
|
|
30 |
|
## special case |
31 |
|
setAs("dgeMatrix", "dgCMatrix", |
32 |
|
function(from) .Call(dense_to_Csparse, from)) |
33 |
|
|
34 |
|
setAs("matrix", "CsparseMatrix", |
35 |
|
function(from) |
36 |
|
.Call(dense_to_Csparse, .Call(dup_mMatrix_as_dgeMatrix, from))) |
37 |
|
|
38 |
|
## special case needed in the Matrix function |
39 |
|
setAs("matrix", "dgCMatrix", |
40 |
|
function(from) { |
41 |
|
storage.mode(from) <- "double" |
42 |
|
.Call(dense_to_Csparse, from) |
43 |
|
}) |
44 |
|
|
45 |
|
setAs("numeric", "CsparseMatrix", |
46 |
|
function(from) |
47 |
|
.Call(dense_to_Csparse, .Call(dup_mMatrix_as_dgeMatrix, from))) |
48 |
|
|
49 |
|
setMethod("as.numeric", signature(x = "ddenseMatrix"), |
50 |
|
function(x, ...) as(x, "dgeMatrix")@x) |
51 |
|
|
52 |
## -- see also ./Matrix.R e.g., for a show() method |
## -- see also ./Matrix.R e.g., for a show() method |
53 |
|
|
54 |
## These methods are the 'fallback' methods for all dense numeric |
## These methods are the 'fallback' methods for all dense numeric |
67 |
setMethod("rcond", signature(x = "ddenseMatrix", type = "character"), |
setMethod("rcond", signature(x = "ddenseMatrix", type = "character"), |
68 |
function(x, type, ...) callGeneric(as(x, "dgeMatrix"), type)) |
function(x, type, ...) callGeneric(as(x, "dgeMatrix"), type)) |
69 |
|
|
70 |
setMethod("t", signature(x = "ddenseMatrix"), |
## Not really useful; now require *identical* class for result: |
71 |
function(x) callGeneric(as(x, "dgeMatrix"))) |
## setMethod("t", signature(x = "ddenseMatrix"), |
72 |
|
## function(x) callGeneric(as(x, "dgeMatrix"))) |
73 |
|
|
74 |
setMethod("tcrossprod", signature(x = "ddenseMatrix"), |
setMethod("tcrossprod", signature(x = "ddenseMatrix", y = "missing"), |
75 |
function(x) callGeneric(as(x, "dgeMatrix"))) |
function(x, y = NULL) callGeneric(as(x, "dgeMatrix"))) |
76 |
|
|
77 |
setMethod("crossprod", signature(x = "ddenseMatrix", y = "missing"), |
setMethod("crossprod", signature(x = "ddenseMatrix", y = "missing"), |
78 |
function(x, y = NULL) callGeneric(as(x, "dgeMatrix"))) |
function(x, y = NULL) callGeneric(as(x, "dgeMatrix"))) |
80 |
setMethod("diag", signature(x = "ddenseMatrix"), |
setMethod("diag", signature(x = "ddenseMatrix"), |
81 |
function(x = 1, nrow, ncol = n) callGeneric(as(x, "dgeMatrix"))) |
function(x = 1, nrow, ncol = n) callGeneric(as(x, "dgeMatrix"))) |
82 |
|
|
83 |
setMethod("solve", signature(a = "ddenseMatrix", b = "missing"), |
## These methods cause an infinite loop in pre-2.4.0 |
84 |
function(a, b, ...) callGeneric(as(a, "dgeMatrix"))) |
## setMethod("solve", signature(a = "ddenseMatrix", b = "missing"), |
85 |
|
## function(a, b, ...) callGeneric(as(a, "dgeMatrix"))) |
86 |
setMethod("solve", signature(a = "ddenseMatrix", b = "ANY"), |
|
87 |
function(a, b, ...) callGeneric(as(a, "dgeMatrix"), b)) |
## setMethod("solve", signature(a = "ddenseMatrix", b = "ANY"), |
88 |
|
## function(a, b, ...) callGeneric(as(a, "dgeMatrix"), b)) |
89 |
|
|
90 |
|
## General method for dense matrix multiplication in case specific methods |
91 |
|
## have not been defined. |
92 |
|
setMethod("%*%", signature(x = "ddenseMatrix", y = "ddenseMatrix"), |
93 |
|
function(x, y) .Call(dgeMatrix_matrix_mm, |
94 |
|
.Call(dup_mMatrix_as_dgeMatrix, x), y, FALSE), |
95 |
|
valueClass = "dgeMatrix") |
96 |
|
|
97 |
setMethod("lu", signature(x = "ddenseMatrix"), |
setMethod("lu", signature(x = "ddenseMatrix"), |
98 |
function(x, ...) callGeneric(as(x, "dgeMatrix"))) |
function(x, ...) callGeneric(as(x, "dgeMatrix"))) |
104 |
function(x, logarithm, ...) |
function(x, logarithm, ...) |
105 |
callGeneric(as(x, "dgeMatrix"), logarithm)) |
callGeneric(as(x, "dgeMatrix"), logarithm)) |
106 |
|
|
107 |
setMethod("expm", signature(x = "ddenseMatrix"), |
## now done for "dMatrix": |
108 |
function(x) callGeneric(as(x, "dgeMatrix"))) |
## setMethod("expm", signature(x = "ddenseMatrix"), |
109 |
|
## function(x) callGeneric(as(x, "dgeMatrix"))) |
110 |
|
|
111 |
setMethod("Schur", signature(x = "ddenseMatrix", vectors = "missing"), |
setMethod("Schur", signature(x = "ddenseMatrix", vectors = "missing"), |
112 |
function(x, vectors, ...) callGeneric(as(x, "dgeMatrix"))) |
function(x, vectors, ...) callGeneric(as(x, "dgeMatrix"))) |
115 |
function(x, vectors, ...) callGeneric(as(x, "dgeMatrix"), vectors)) |
function(x, vectors, ...) callGeneric(as(x, "dgeMatrix"), vectors)) |
116 |
|
|
117 |
|
|
118 |
|
## Cheap version: work via "dgeMatrix" and use the group methods there: |
119 |
|
## FIXME(?): try to preserve "symmetric", "triangular", ... |
120 |
|
setMethod("Arith", ## "+", "-", "*", "^", "%%", "%/%", "/" |
121 |
|
signature(e1 = "ddenseMatrix", e2 = "ddenseMatrix"), |
122 |
|
function(e1, e2) callGeneric(as(e1, "dgeMatrix"), |
123 |
|
as(e2, "dgeMatrix"))) |
124 |
|
setMethod("Arith", |
125 |
|
signature(e1 = "ddenseMatrix", e2 = "numeric"), |
126 |
|
function(e1, e2) callGeneric(as(e1, "dgeMatrix"), e2)) |
127 |
|
setMethod("Arith", |
128 |
|
signature(e1 = "numeric", e2 = "ddenseMatrix"), |
129 |
|
function(e1, e2) callGeneric(e1, as(e2, "dgeMatrix"))) |
130 |
|
|
131 |
|
setMethod("Math", |
132 |
|
signature(x = "ddenseMatrix"), |
133 |
|
function(x) callGeneric(as(x, "dgeMatrix"))) |
134 |
|
|
135 |
|
|
136 |
|
|
137 |
|
### for R 2.2.x (and later): -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- |
138 |
|
|
139 |
|
### cbind2 |
140 |
|
setMethod("cbind2", signature(x = "ddenseMatrix", y = "numeric"), |
141 |
|
function(x, y) { |
142 |
|
d <- dim(x); nr <- d[1]; nc <- d[2] |
143 |
|
y <- rep(y, length.out = nr) # 'silent procrustes' |
144 |
|
## beware of (packed) triangular, symmetric, ... |
145 |
|
x <- as(x, "dgeMatrix") |
146 |
|
x@x <- c(x@x, as.double(y)) |
147 |
|
x@Dim[2] <- nc + 1:1 |
148 |
|
if(is.character(dn <- x@Dimnames[[2]])) |
149 |
|
x@Dimnames[[2]] <- c(dn, "") |
150 |
|
x |
151 |
|
}) |
152 |
|
## the same, (x,y) <-> (y,x): |
153 |
|
setMethod("cbind2", signature(x = "numeric", y = "ddenseMatrix"), |
154 |
|
function(x, y) { |
155 |
|
d <- dim(y); nr <- d[1]; nc <- d[2] |
156 |
|
x <- rep(x, length.out = nr) |
157 |
|
y <- as(y, "dgeMatrix") |
158 |
|
y@x <- c(as.double(x), y@x) |
159 |
|
y@Dim[2] <- nc + 1:1 |
160 |
|
if(is.character(dn <- y@Dimnames[[2]])) |
161 |
|
y@Dimnames[[2]] <- c("", dn) |
162 |
|
y |
163 |
|
}) |
164 |
|
|
165 |
|
setMethod("cbind2", signature(x = "ddenseMatrix", y = "matrix"), |
166 |
|
function(x, y) callGeneric(x, as(y, "dgeMatrix"))) |
167 |
|
setMethod("cbind2", signature(x = "matrix", y = "ddenseMatrix"), |
168 |
|
function(x, y) callGeneric(as(x, "dgeMatrix"), y)) |
169 |
|
|
170 |
|
setMethod("cbind2", signature(x = "ddenseMatrix", y = "ddenseMatrix"), |
171 |
|
function(x, y) { |
172 |
|
nr <- rowCheck(x,y) |
173 |
|
ncx <- x@Dim[2] |
174 |
|
ncy <- y@Dim[2] |
175 |
|
## beware of (packed) triangular, symmetric, ... |
176 |
|
hasDN <- !is.null(dnx <- dimnames(x)) | |
177 |
|
!is.null(dny <- dimnames(y)) |
178 |
|
x <- as(x, "dgeMatrix") |
179 |
|
y <- as(y, "dgeMatrix") |
180 |
|
x@x <- c(x@x, y@x) |
181 |
|
x@Dim[2] <- ncx + ncy |
182 |
|
if(hasDN) { |
183 |
|
## R and S+ are different in which names they take |
184 |
|
## if they differ -- but there's no warning in any case |
185 |
|
rn <- if(!is.null(dnx[[1]])) dnx[[1]] else dny[[1]] |
186 |
|
cx <- dnx[[2]] ; cy <- dny[[2]] |
187 |
|
cn <- if(is.null(cx) && is.null(cy)) NULL |
188 |
|
else c(if(!is.null(cx)) cx else rep.int("", ncx), |
189 |
|
if(!is.null(cy)) cy else rep.int("", ncy)) |
190 |
|
x@Dimnames <- list(rn, cn) |
191 |
|
} |
192 |
|
x |
193 |
|
}) |
194 |
|
|
195 |
|
### rbind2 -- analogous to cbind2 --- more to do for @x though: |
196 |
|
|
197 |
|
setMethod("rbind2", signature(x = "ddenseMatrix", y = "numeric"), |
198 |
|
function(x, y) { |
199 |
|
if(is.character(dn <- x@Dimnames[[1]])) dn <- c(dn, "") |
200 |
|
new("dgeMatrix", Dim = x@Dim + 1:0, |
201 |
|
Dimnames = list(dn, x@Dimnames[[2]]), |
202 |
|
x = c(rbind2(as(x,"matrix"), y))) |
203 |
|
}) |
204 |
|
## the same, (x,y) <-> (y,x): |
205 |
|
setMethod("rbind2", signature(x = "numeric", y = "ddenseMatrix"), |
206 |
|
function(x, y) { |
207 |
|
if(is.character(dn <- y@Dimnames[[1]])) dn <- c("", dn) |
208 |
|
new("dgeMatrix", Dim = y@Dim + 1:0, |
209 |
|
Dimnames = list(dn, y@Dimnames[[2]]), |
210 |
|
x = c(rbind2(x, as(y,"matrix")))) |
211 |
|
}) |
212 |
|
|
213 |
|
setMethod("rbind2", signature(x = "ddenseMatrix", y = "matrix"), |
214 |
|
function(x, y) callGeneric(x, as(y, "dgeMatrix"))) |
215 |
|
setMethod("rbind2", signature(x = "matrix", y = "ddenseMatrix"), |
216 |
|
function(x, y) callGeneric(as(x, "dgeMatrix"), y)) |
217 |
|
|
218 |
|
setMethod("rbind2", signature(x = "ddenseMatrix", y = "ddenseMatrix"), |
219 |
|
function(x, y) { |
220 |
|
nc <- colCheck(x,y) |
221 |
|
nrx <- x@Dim[1] |
222 |
|
nry <- y@Dim[1] |
223 |
|
dn <- |
224 |
|
if(!is.null(dnx <- dimnames(x)) | |
225 |
|
!is.null(dny <- dimnames(y))) { |
226 |
|
## R and S+ are different in which names they take |
227 |
|
## if they differ -- but there's no warning in any case |
228 |
|
list(if(is.null(rx <- dnx[[1]]) && is.null(ry <- dny[[1]])) |
229 |
|
NULL else |
230 |
|
c(if(!is.null(rx)) rx else rep.int("", nrx), |
231 |
|
if(!is.null(ry)) ry else rep.int("", nry)), |
232 |
|
if(!is.null(dnx[[2]])) dnx[[2]] else dny[[2]]) |
233 |
|
|
234 |
|
} else list(NULL, NULL) |
235 |
|
## beware of (packed) triangular, symmetric, ... |
236 |
|
new("dgeMatrix", Dim = c(nrx + nry, nc), Dimnames = dn, |
237 |
|
x = c(rbind2(as(x,"matrix"), as(y,"matrix")))) |
238 |
|
}) |
239 |
|
|
240 |
|
### FIXME: band() et al should be extended from "ddense" to "dense" ! |
241 |
|
### However, needs much work to generalize dup_mMatrix_as_dgeMatrix() |
242 |
|
|
243 |
|
## NB: have extra tril(), triu() methods for symmetric ["dsy" and "dsp"] and |
244 |
|
## for triangular ["dtr" and "dtp"] |
245 |
|
setMethod("tril", "ddenseMatrix", |
246 |
|
function(x, k = 0, ...) { |
247 |
|
k <- as.integer(k[1]) |
248 |
|
dd <- dim(x); sqr <- dd[1] == dd[2] |
249 |
|
stopifnot(-dd[1] <= k, k <= dd[1]) # had k <= 0 |
250 |
|
## returns "lower triangular" if k <= 0 && sqr |
251 |
|
.Call(ddense_band, x, -dd[1], k) |
252 |
|
}) |
253 |
|
|
254 |
|
setMethod("triu", "ddenseMatrix", |
255 |
|
function(x, k = 0, ...) { |
256 |
|
k <- as.integer(k[1]) |
257 |
|
dd <- dim(x); sqr <- dd[1] == dd[2] |
258 |
|
stopifnot(-dd[1] <= k, k <= dd[1]) # had k >= 0 |
259 |
|
## returns "upper triangular" if k >= 0 |
260 |
|
.Call(ddense_band, x, k, dd[2]) |
261 |
|
}) |
262 |
|
|
263 |
|
setMethod("band", "ddenseMatrix", |
264 |
|
function(x, k1, k2, ...) { |
265 |
|
k1 <- as.integer(k1[1]) |
266 |
|
k2 <- as.integer(k2[1]) |
267 |
|
dd <- dim(x); sqr <- dd[1] == dd[2] |
268 |
|
stopifnot(-dd[1] <= k1, k1 <= k2, k2 <= dd[1]) |
269 |
|
r <- .Call(ddense_band, x, k1, k2) |
270 |
|
if (k1 < 0 && k1 == -k2 && isSymmetric(x)) ## symmetric |
271 |
|
as(r, paste(.M.kind(x), "syMatrix", sep='')) |
272 |
|
else |
273 |
|
r |
274 |
|
}) |