1 |
#### Toplevel ``virtual'' class "Matrix" |
#### Toplevel ``virtual'' class "Matrix" |
2 |
|
|
|
## probably not needed eventually: |
|
|
setAs(from = "Matrix", to = "matrix", |
|
|
function(from) { |
|
|
if(length(d <- dim(from)) != 2) stop("dim(.) has not length 2") |
|
|
array(as.numeric(NA), dim = d, dimnames = dimnames(from)) |
|
|
}) |
|
3 |
|
|
4 |
prMatrix <- |
### Virtual coercions -- via smart "helpers" (-> ./Auxiliaries.R) |
5 |
## private function to be used as show() method possibly more than once |
|
6 |
function(object) { |
setAs("Matrix", "sparseMatrix", function(from) as_Csparse(from)) |
7 |
|
setAs("Matrix", "denseMatrix", function(from) as_dense(from)) |
8 |
|
|
9 |
|
## ## probably not needed eventually: |
10 |
|
## setAs(from = "ddenseMatrix", to = "matrix", |
11 |
|
## function(from) { |
12 |
|
## if(length(d <- dim(from)) != 2) stop("dim(.) has not length 2") |
13 |
|
## array(from@x, dim = d, dimnames = dimnames(from)) |
14 |
|
## }) |
15 |
|
|
16 |
|
## should propagate to all subclasses: |
17 |
|
setMethod("as.matrix", signature(x = "Matrix"), function(x) as(x, "matrix")) |
18 |
|
## for 'Matrix' objects, as.array() should be equivalent: |
19 |
|
setMethod("as.array", signature(x = "Matrix"), function(x) as(x, "matrix")) |
20 |
|
|
21 |
|
## head and tail apply to all Matrix objects for which subscripting is allowed: |
22 |
|
## if(paste(R.version$major, R.version$minor, sep=".") < "2.4") { |
23 |
|
setMethod("head", signature(x = "Matrix"), utils:::head.matrix) |
24 |
|
setMethod("tail", signature(x = "Matrix"), utils:::tail.matrix) |
25 |
|
## } else { # R 2.4.0 and newer |
26 |
|
## setMethod("head", signature(x = "Matrix"), utils::head.matrix) |
27 |
|
## setMethod("tail", signature(x = "Matrix"), utils::tail.matrix) |
28 |
|
## } |
29 |
|
|
30 |
|
## slow "fall back" method {subclasses should have faster ones}: |
31 |
|
setMethod("as.vector", signature(x = "Matrix", mode = "missing"), |
32 |
|
function(x) as.vector(as(x, "matrix"))) |
33 |
|
|
34 |
|
## mainly need these for "dMatrix" or "lMatrix" respectively, but why not general: |
35 |
|
setMethod("as.numeric", signature(x = "Matrix"), |
36 |
|
function(x, ...) as.numeric(as.vector(x))) |
37 |
|
setMethod("as.logical", signature(x = "Matrix"), |
38 |
|
function(x, ...) as.logical(as.vector(x))) |
39 |
|
|
40 |
|
|
41 |
|
## Note that isSymmetric is *not* exported |
42 |
|
## but that "base" has an isSymmetric() S3-generic since R 2.3.0 |
43 |
|
setMethod("isSymmetric", signature(object = "symmetricMatrix"), |
44 |
|
function(object,tol) TRUE) |
45 |
|
setMethod("isSymmetric", signature(object = "triangularMatrix"), |
46 |
|
## TRUE iff diagonal: |
47 |
|
function(object,tol) isDiagonal(object)) |
48 |
|
|
49 |
|
if(paste(R.version$major, R.version$minor, sep=".") < "2.3") |
50 |
|
## need a "matrix" method as in R 2.3 and later |
51 |
|
setMethod("isSymmetric", signature(object = "matrix"), |
52 |
|
function(object, tol = 100*.Machine$double.eps, ...) |
53 |
|
{ |
54 |
|
## pretest: is it square? |
55 |
d <- dim(object) |
d <- dim(object) |
56 |
cat(paste(d, collapse= " x "), " Matrix of class ", |
if(d[1] != d[2]) return(FALSE) |
57 |
sQuote(class(object)),"\n", sep='') |
## for `broken' all.equal in R <= 2.2.x: |
58 |
m <- as(object, "matrix") |
dn <- dimnames(object) |
59 |
maxp <- getOption("max.print") |
if(!identical(dn[1], dn[2])) return(FALSE) |
60 |
if(prod(d) <= maxp) print(m) |
test <- |
61 |
else { ## d[1] > maxp / d[2] >= nr : |
if(is.complex(object)) |
62 |
nr <- maxp %/% d[2] |
all.equal.numeric(object, Conj(t(object)), tol = tol, ...) |
63 |
n2 <- ceiling(nr / 2) |
else # numeric, character, .. |
64 |
print(head(m, max(1, n2))) |
all.equal(object, t(object), tol = tol, ...) |
65 |
cat("\n ..........\n\n") |
isTRUE(test) |
66 |
print(tail(m, max(1, nr - n2))) |
}) |
67 |
} |
|
68 |
## DEBUG: cat("str(.):\n") ; str(object) |
|
69 |
invisible() |
setMethod("isTriangular", signature(object = "triangularMatrix"), |
70 |
} |
function(object, ...) TRUE) |
71 |
|
|
72 |
setMethod("show", signature(object = "ddenseMatrix"), prMatrix) |
setMethod("isTriangular", signature(object = "matrix"), isTriMat) |
73 |
## this may go away {since sparse matrices need something better!} : |
|
74 |
setMethod("show", signature(object = "Matrix"), prMatrix) |
setMethod("isDiagonal", signature(object = "matrix"), .is.diagonal) |
75 |
|
|
76 |
|
|
77 |
|
|
78 |
setMethod("dim", signature(x = "Matrix"), |
setMethod("dim", signature(x = "Matrix"), |
79 |
function(x) x@Dim, valueClass = "integer") |
function(x) x@Dim, valueClass = "integer") |
93 |
setMethod("dimnames<-", signature(x = "Matrix", value = "list"), |
setMethod("dimnames<-", signature(x = "Matrix", value = "list"), |
94 |
dimnamesGets) |
dimnamesGets) |
95 |
|
|
96 |
|
setMethod("unname", signature("Matrix", force="missing"), |
97 |
|
function(obj) { obj@Dimnames <- list(NULL,NULL); obj}) |
98 |
|
|
99 |
Matrix <- |
Matrix <- |
100 |
function (data = NA, nrow = 1, ncol = 1, byrow = FALSE, dimnames = NULL) |
function (data = NA, nrow = 1, ncol = 1, byrow = FALSE, dimnames = NULL, |
101 |
|
sparse = NULL, forceCheck = FALSE) |
102 |
{ |
{ |
103 |
if (is(data, "Matrix")) return(data) |
sparseDefault <- function(m) |
104 |
if (is.matrix(data)) { val <- data } |
prod(dim(m)) > 2*sum(as(m, "matrix") != 0) |
105 |
else { ## cut & paste from "base::matrix" : |
|
106 |
|
i.M <- is(data, "Matrix") |
107 |
|
if(is.null(sparse) && (i.M || is(data, "matrix"))) |
108 |
|
sparse <- sparseDefault(data) |
109 |
|
|
110 |
|
doDN <- TRUE |
111 |
|
if (i.M && !forceCheck) { |
112 |
|
sM <- is(data,"sparseMatrix") |
113 |
|
if((sparse && sM) || (!sparse && !sM)) |
114 |
|
return(data) |
115 |
|
## else : convert dense <-> sparse -> at end |
116 |
|
} |
117 |
|
else if (!is.matrix(data)) { ## cut & paste from "base::matrix" : |
118 |
if (missing(nrow)) |
if (missing(nrow)) |
119 |
nrow <- ceiling(length(data)/ncol) |
nrow <- ceiling(length(data)/ncol) |
120 |
else if (missing(ncol)) |
else if (missing(ncol)) |
121 |
ncol <- ceiling(length(data)/nrow) |
ncol <- ceiling(length(data)/nrow) |
122 |
val <- .Internal(matrix(data, nrow, ncol, byrow)) |
if(length(data) == 1 && data == 0 && !identical(sparse,FALSE)) { |
123 |
dimnames(val) <- dimnames |
if(is.null(sparse)) sparse <- TRUE |
124 |
} |
## will be sparse: do NOT construct full matrix! |
125 |
as(val, "dgeMatrix") |
data <- new(if(is.numeric(data)) "dgTMatrix" else |
126 |
} |
if(is.logical(data)) "lgTMatrix" else |
127 |
|
stop("invalid 'data'"), |
128 |
|
Dim = as.integer(c(nrow,ncol)), |
129 |
|
Dimnames = if(is.null(dimnames)) list(NULL,NULL) |
130 |
|
else dimnames) |
131 |
|
} else { ## normal case |
132 |
|
data <- .Internal(matrix(data, nrow, ncol, byrow)) |
133 |
|
if(is.null(sparse)) |
134 |
|
sparse <- sparseDefault(data) |
135 |
|
dimnames(data) <- dimnames |
136 |
|
} |
137 |
|
doDN <- FALSE |
138 |
|
} |
139 |
|
## 'data' is now a "matrix" or "Matrix" |
140 |
|
if (doDN && !is.null(dimnames)) |
141 |
|
dimnames(data) <- dimnames |
142 |
|
|
143 |
|
## check for symmetric / triangular / diagonal : |
144 |
|
isSym <- isSymmetric(data) |
145 |
|
if((isTri <- !isSym)) |
146 |
|
isTri <- isTriangular(data) |
147 |
|
isDiag <- isSym # cannot be diagonal if it isn't symmetric |
148 |
|
if(isDiag) |
149 |
|
isDiag <- isDiagonal(data) |
150 |
|
|
151 |
|
### TODO: Compare with as.Matrix() and its tests in ./dgeMatrix.R |
152 |
|
|
153 |
|
## Find proper matrix class 'cl' |
154 |
|
cl <- |
155 |
|
if(isDiag) |
156 |
|
"diagonalMatrix" # -> will automatically check for type |
157 |
|
else { |
158 |
|
## consider it's type |
159 |
|
ctype <- |
160 |
|
if(is(data,"Matrix")) class(data) |
161 |
|
else { |
162 |
|
if("complex" == (ctype <- typeof(data))) |
163 |
|
"z" else ctype |
164 |
|
} |
165 |
|
ctype <- substr(ctype, 1,1) # "d", "l", "i" or "z" |
166 |
|
if(ctype == "z") |
167 |
|
stop("complex matrices not yet implemented in Matrix package") |
168 |
|
if(ctype == "i") { |
169 |
|
warning("integer matrices not yet implemented in 'Matrix'; ", |
170 |
|
"using 'double' ones'") |
171 |
|
ctype <- "d" |
172 |
|
} |
173 |
|
paste(ctype, |
174 |
|
if(sparse) { |
175 |
|
if(isSym) "sCMatrix" else |
176 |
|
if(isTri) "tCMatrix" else "gCMatrix" |
177 |
|
} else { ## dense |
178 |
|
if(isSym) "syMatrix" else |
179 |
|
if(isTri) "trMatrix" else "geMatrix" |
180 |
|
}, sep="") |
181 |
|
} |
182 |
|
|
183 |
|
## Now coerce and return |
184 |
|
as(data, cl) |
185 |
|
} |
186 |
|
|
187 |
|
## Methods for operations where one argument is numeric |
188 |
|
|
189 |
|
## Using as.matrix() and rbind() |
190 |
|
## in order to get dimnames from names {at least potentially}: |
191 |
|
|
192 |
|
setMethod("%*%", signature(x = "Matrix", y = "numeric"), |
193 |
|
function(x, y) callGeneric(x, as.matrix(y))) |
194 |
|
|
195 |
|
setMethod("%*%", signature(x = "numeric", y = "Matrix"), |
196 |
|
function(x, y) callGeneric(rbind(x), y)) |
197 |
|
|
198 |
|
setMethod("crossprod", signature(x = "Matrix", y = "numeric"), |
199 |
|
function(x, y = NULL) callGeneric(x, as.matrix(y))) |
200 |
|
setMethod("crossprod", signature(x = "numeric", y = "Matrix"), |
201 |
|
function(x, y = NULL) callGeneric(as.matrix(x), y)) |
202 |
|
|
203 |
|
## The as.matrix() promotion seems illogical to MM, |
204 |
|
## but is according to help(tcrossprod, package = "base") : |
205 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "numeric"), |
206 |
|
function(x, y = NULL) callGeneric(x, as.matrix(y))) |
207 |
|
setMethod("tcrossprod", signature(x = "numeric", y = "Matrix"), |
208 |
|
function(x, y = NULL) callGeneric(as.matrix(x), y)) |
209 |
|
|
210 |
|
setMethod("solve", signature(a = "Matrix", b = "numeric"), |
211 |
|
function(a, b, ...) callGeneric(a, as.matrix(b))) |
212 |
|
|
213 |
|
## bail-out methods in order to get better error messages |
214 |
|
setMethod("%*%", signature(x = "Matrix", y = "Matrix"), |
215 |
|
function (x, y) |
216 |
|
stop(gettextf('not-yet-implemented method for <%s> %%*%% <%s>', |
217 |
|
class(x), class(y)))) |
218 |
|
|
219 |
|
setMethod("crossprod", signature(x = "Matrix", y = "ANY"), |
220 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
221 |
|
setMethod("crossprod", signature(x = "ANY", y = "Matrix"), |
222 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
223 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "ANY"), |
224 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
225 |
|
setMethod("tcrossprod", signature(x = "ANY", y = "Matrix"), |
226 |
|
function (x, y = NULL) .bail.out.2(.Generic, class(x), class(y))) |
227 |
|
|
228 |
|
## cheap fallbacks |
229 |
|
setMethod("crossprod", signature(x = "Matrix", y = "Matrix"), |
230 |
|
function(x, y = NULL) t(x) %*% y) |
231 |
|
setMethod("tcrossprod", signature(x = "Matrix", y = "Matrix"), |
232 |
|
function(x, y = NULL) x %*% t(y)) |
233 |
|
|
234 |
|
## There are special sparse methods; this is a "fall back": |
235 |
|
setMethod("kronecker", signature(X = "Matrix", Y = "ANY", |
236 |
|
FUN = "ANY", make.dimnames = "ANY"), |
237 |
|
function(X, Y, FUN, make.dimnames, ...) { |
238 |
|
X <- as(X, "matrix") ; Matrix(callGeneric()) }) |
239 |
|
setMethod("kronecker", signature(X = "ANY", Y = "Matrix", |
240 |
|
FUN = "ANY", make.dimnames = "ANY"), |
241 |
|
function(X, Y, FUN, make.dimnames, ...) { |
242 |
|
Y <- as(Y, "matrix") ; Matrix(callGeneric()) }) |
243 |
|
|
244 |
|
|
245 |
|
setMethod("diag", signature(x = "Matrix"), |
246 |
|
function(x, nrow, ncol) .bail.out.1(.Generic, class(x))) |
247 |
|
setMethod("t", signature(x = "Matrix"), |
248 |
|
function(x) .bail.out.1(.Generic, class(x))) |
249 |
|
|
250 |
|
## Group Methods |
251 |
|
setMethod("+", signature(e1 = "Matrix", e2 = "missing"), function(e1) e1) |
252 |
|
## "fallback": |
253 |
|
setMethod("-", signature(e1 = "Matrix", e2 = "missing"), |
254 |
|
function(e1) { |
255 |
|
warning("inefficient method used for \"- e1\"") |
256 |
|
0-e1 |
257 |
|
}) |
258 |
|
|
259 |
|
## bail-outs: |
260 |
|
setMethod("Compare", signature(e1 = "Matrix", e2 = "Matrix"), |
261 |
|
function(e1, e2) { |
262 |
|
d <- dimCheck(e1,e2) |
263 |
|
.bail.out.2(.Generic, class(e1), class(e2)) |
264 |
|
}) |
265 |
|
setMethod("Compare", signature(e1 = "Matrix", e2 = "ANY"), |
266 |
|
function(e1, e2) .bail.out.2(.Generic, class(e1), class(e2))) |
267 |
|
setMethod("Compare", signature(e1 = "ANY", e2 = "Matrix"), |
268 |
|
function(e1, e2) .bail.out.2(.Generic, class(e1), class(e2))) |
269 |
|
|
|
if(FALSE) { ##--- not-yet used -- {almost same code also in ./dgeMatrix.R } |
|
270 |
|
|
|
## utility for as.Matrix() {which is currently invalid } |
|
|
Matrix.class <- function(x, tol = 0, symmetry = TRUE, unit.diagonal = TRUE, |
|
|
triangularity = c(TRUE, TRUE), |
|
|
orthogonality = c(TRUE, TRUE), |
|
|
normality = c(TRUE, TRUE)) |
|
|
{ |
|
|
val <- "Matrix" |
|
|
x <- as.matrix(x) |
|
|
if (symmetry) { |
|
|
if (is.Hermitian(x, tol)) val <- c("Hermitian", val) |
|
|
} |
|
|
if (triangularity[1]) { |
|
|
if (is.LowerTriangular(x, tol)) { |
|
|
val <- c("LowerTriangular", val) |
|
|
if (unit.diagonal) |
|
|
if (max(Mod(diag(x) - 1)) <= tol) |
|
|
val <- c("UnitLowerTriangular", val) |
|
|
} |
|
|
} |
|
|
if (triangularity[2]) { |
|
|
if (is.UpperTriangular(x, tol)) { |
|
|
val <- c("UpperTriangular", val) |
|
|
if (unit.diagonal) |
|
|
if (max(Mod(diag(x) - 1)) <= tol) |
|
|
val <- c("UnitUpperTriangular", val) |
|
|
} |
|
|
} |
|
|
if (orthogonality[1]) { |
|
|
if (is.ColOrthonormal(x, tol)) { |
|
|
val <- c("ColOrthoNormal", "ColOrthogonal", val) |
|
|
} else { |
|
|
if (Orthogonal.test(x, normal = FALSE) <= tol) |
|
|
val <- c("ColOrthogonal", val) |
|
|
} |
|
|
} |
|
|
if (orthogonality[2]) { |
|
|
if (normality[2] && is.RowOrthonormal(x, tol)) { |
|
|
val <- c("RowOrthoNormal", "RowOrthogonal", val) |
|
|
} else { |
|
|
if (Orthogonal.test(x, byrow = TRUE, normal = FALSE) <= tol) |
|
|
val <- c("RowOrthogonal", val) |
|
|
} |
|
|
} |
|
|
val |
|
|
} |
|
271 |
|
|
272 |
as.Matrix <- function(x, tol = .Machine$double.eps) |
### -------------------------------------------------------------------------- |
273 |
{ |
### |
274 |
asObject(if (inherits(x, "Matrix")) x else as.matrix(x), |
### Subsetting "[" and |
275 |
Matrix.class(x, tol = tol)) |
### SubAssign "[<-" : The "missing" cases can be dealt with here, "at the top": |
276 |
} |
|
277 |
|
## Using "index" for indices should allow |
278 |
|
## integer (numeric), logical, or character (names!) indices : |
279 |
|
|
280 |
|
## "x[]": |
281 |
|
setMethod("[", signature(x = "Matrix", |
282 |
|
i = "missing", j = "missing", drop = "ANY"), |
283 |
|
function (x, i, j, drop) x) |
284 |
|
|
285 |
|
## missing 'drop' --> 'drop = TRUE' |
286 |
|
## ----------- |
287 |
|
## select rows |
288 |
|
setMethod("[", signature(x = "Matrix", i = "index", j = "missing", |
289 |
|
drop = "missing"), |
290 |
|
function(x,i,j, drop) callGeneric(x, i=i, drop= TRUE)) |
291 |
|
## select columns |
292 |
|
setMethod("[", signature(x = "Matrix", i = "missing", j = "index", |
293 |
|
drop = "missing"), |
294 |
|
function(x,i,j, drop) callGeneric(x, j=j, drop= TRUE)) |
295 |
|
setMethod("[", signature(x = "Matrix", i = "index", j = "index", |
296 |
|
drop = "missing"), |
297 |
|
function(x,i,j, drop) callGeneric(x, i=i, j=j, drop= TRUE)) |
298 |
|
|
299 |
|
## bail out if any of (i,j,drop) is "non-sense" |
300 |
|
setMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", drop = "ANY"), |
301 |
|
function(x,i,j, drop) |
302 |
|
stop("invalid or not-yet-implemented 'Matrix' subsetting")) |
303 |
|
|
304 |
|
## "logical *vector* indexing, such as M [ M >= 10 ] : |
305 |
|
setMethod("[", signature(x = "Matrix", i = "lMatrix", j = "missing", |
306 |
|
drop = "ANY"), |
307 |
|
function (x, i, j, drop) { |
308 |
|
as(x, geClass(x))@x[as.vector(i)] |
309 |
|
## -> error when lengths don't match |
310 |
|
}) |
311 |
|
|
312 |
|
## FIXME: The following is good for M [ <logical> ] |
313 |
|
## *BUT* it also triggers for M [ <logical> , ] where it is *WRONG* |
314 |
|
## using nargs() does not help: it gives '3' for both cases |
315 |
|
if(FALSE) |
316 |
|
setMethod("[", signature(x = "Matrix", i = "logical", j = "missing", |
317 |
|
drop = "ANY"), |
318 |
|
function (x, i, j, drop) { |
319 |
|
## DEBUG |
320 |
|
cat("[(Matrix,i,..): nargs=", nargs(),"\n") |
321 |
|
as(x, geClass(x))@x[i] }) |
322 |
|
|
323 |
|
|
324 |
|
## "FIXME:" |
325 |
|
## How can we get at A[ ij ] where ij is (i,j) 2-column matrix? |
326 |
|
## and A[ LL ] where LL is a logical *vector* |
327 |
|
## -> [.data.frame uses nargs() - can we do this in the *generic* ? |
328 |
|
|
329 |
|
|
330 |
|
### "[<-" : ----------------- |
331 |
|
|
332 |
|
## x[] <- value : |
333 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "missing", j = "missing", |
334 |
|
value = "ANY"),## double/logical/... |
335 |
|
function (x, value) { |
336 |
|
x@x <- value |
337 |
|
validObject(x)# check if type and lengths above match |
338 |
|
x |
339 |
|
}) |
340 |
|
|
341 |
|
## Method for all 'Matrix' kinds (rather than incomprehensible error messages); |
342 |
|
## (ANY,ANY,ANY) is used when no `real method' is implemented : |
343 |
|
setReplaceMethod("[", signature(x = "Matrix", i = "ANY", j = "ANY", |
344 |
|
value = "ANY"), |
345 |
|
function (x, i, j, value) { |
346 |
|
if(!is.atomic(value)) |
347 |
|
stop("RHS 'value' must match matrix class ", class(x)) |
348 |
|
else stop("not-yet-implemented 'Matrix[<-' method") |
349 |
|
}) |
350 |
|
|
351 |
|
|
352 |
}## not-yet used |
## The trivial methods : |
353 |
|
setMethod("cbind2", signature(x = "Matrix", y = "NULL"), |
354 |
|
function(x, y) x) |
355 |
|
setMethod("cbind2", signature(x = "Matrix", y = "missing"), |
356 |
|
function(x, y) x) |
357 |
|
setMethod("cbind2", signature(x = "NULL", y="Matrix"), |
358 |
|
function(x, y) x) |
359 |
|
|
360 |
|
setMethod("rbind2", signature(x = "Matrix", y = "NULL"), |
361 |
|
function(x, y) x) |
362 |
|
setMethod("rbind2", signature(x = "Matrix", y = "missing"), |
363 |
|
function(x, y) x) |
364 |
|
setMethod("rbind2", signature(x = "NULL", y="Matrix"), |
365 |
|
function(x, y) x) |
366 |
|
|
367 |
|
## Makes sure one gets x decent error message for the unimplemented cases: |
368 |
|
setMethod("cbind2", signature(x = "Matrix", y = "Matrix"), |
369 |
|
function(x, y) { |
370 |
|
rowCheck(x,y) |
371 |
|
stop(gettextf("cbind2() method for (%s,%s) not-yet defined", |
372 |
|
class(x), class(y))) |
373 |
|
}) |
374 |
|
|
375 |
|
## Use a working fall back {particularly useful for sparse}: |
376 |
|
## FIXME: implement rbind2 via "cholmod" for C* and Tsparse ones |
377 |
|
setMethod("rbind2", signature(x = "Matrix", y = "Matrix"), |
378 |
|
function(x, y) { |
379 |
|
colCheck(x,y) |
380 |
|
t(cbind2(t(x), t(y))) |
381 |
|
}) |