- col/rowMaxs
- col/rowMeans2
- col/rowMedians
- col/rowMins
- col/rowRanges
- col/rowSds
- col/rowVars
... | ... |
@@ -15,20 +15,13 @@ export(colIQRs) |
15 | 15 |
export(colLogSumExps) |
16 | 16 |
export(colMadDiffs) |
17 | 17 |
export(colMads) |
18 |
-export(colMaxs) |
|
19 |
-export(colMeans2) |
|
20 |
-export(colMedians) |
|
21 |
-export(colMins) |
|
22 | 18 |
export(colOrderStats) |
23 | 19 |
export(colProds) |
24 | 20 |
export(colQuantiles) |
25 |
-export(colRanges) |
|
26 | 21 |
export(colRanks) |
27 | 22 |
export(colSdDiffs) |
28 |
-export(colSds) |
|
29 | 23 |
export(colTabulates) |
30 | 24 |
export(colVarDiffs) |
31 |
-export(colVars) |
|
32 | 25 |
export(colWeightedMads) |
33 | 26 |
export(colWeightedMeans) |
34 | 27 |
export(colWeightedMedians) |
... | ... |
@@ -49,21 +42,13 @@ export(rowIQRs) |
49 | 42 |
export(rowLogSumExps) |
50 | 43 |
export(rowMadDiffs) |
51 | 44 |
export(rowMads) |
52 |
-export(rowMaxs) |
|
53 |
-export(rowMeans2) |
|
54 |
-export(rowMedians) |
|
55 |
-export(rowMins) |
|
56 | 45 |
export(rowOrderStats) |
57 | 46 |
export(rowProds) |
58 | 47 |
export(rowQuantiles) |
59 |
-export(rowRanges) |
|
60 | 48 |
export(rowRanks) |
61 | 49 |
export(rowSdDiffs) |
62 |
-export(rowSds) |
|
63 |
-export(rowSums2) |
|
64 | 50 |
export(rowTabulates) |
65 | 51 |
export(rowVarDiffs) |
66 |
-export(rowVars) |
|
67 | 52 |
export(rowWeightedMads) |
68 | 53 |
export(rowWeightedMeans) |
69 | 54 |
export(rowWeightedMedians) |
... | ... |
@@ -2,9 +2,7 @@ |
2 | 2 |
|
3 | 3 |
# Sum |
4 | 4 |
|
5 |
- |
|
6 | 5 |
#' @inherit MatrixGenerics::colSums2 |
7 |
-#' |
|
8 | 6 |
#' @export |
9 | 7 |
setMethod("colSums2", signature(x = "dgCMatrix"), |
10 | 8 |
function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
... | ... |
@@ -18,65 +16,68 @@ setMethod("colSums2", signature(x = "dgCMatrix"), |
18 | 16 |
}) |
19 | 17 |
|
20 | 18 |
|
21 |
- |
|
22 | 19 |
# Mean |
23 | 20 |
|
24 |
-#' @inherit matrixStats::colMeans2 |
|
25 |
-#' @export |
|
26 |
-setGeneric("colMeans2", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
27 |
- matrixStats::colMeans2(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
28 |
-}) |
|
29 |
- |
|
30 |
- |
|
31 |
-#' @rdname colMeans2 |
|
21 |
+#' @inherit MatrixGenerics::colMeans2 |
|
32 | 22 |
#' @export |
33 | 23 |
setMethod("colMeans2", signature(x = "dgCMatrix"), |
34 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
35 |
- dgCMatrix_colMeans2(x, na_rm = na.rm)) |
|
24 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
25 |
+ if(! is.null(rows)){ |
|
26 |
+ x <- x[rows, , drop = FALSE] |
|
27 |
+ } |
|
28 |
+ if(! is.null(cols)){ |
|
29 |
+ x <- x[, cols, drop = FALSE] |
|
30 |
+ } |
|
31 |
+ dgCMatrix_colMeans2(x, na_rm = na.rm) |
|
32 |
+}) |
|
36 | 33 |
|
37 | 34 |
|
38 | 35 |
# Median |
39 | 36 |
|
40 |
-#' @inherit matrixStats::colMedians |
|
37 |
+#' @inherit MatrixGenerics::colMedians |
|
41 | 38 |
#' @export |
42 |
-setGeneric("colMedians", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
43 |
- matrixStats::colMedians(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
39 |
+setMethod("colMedians", signature(x = "dgCMatrix"), |
|
40 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
41 |
+ if(! is.null(rows)){ |
|
42 |
+ x <- x[rows, , drop = FALSE] |
|
43 |
+ } |
|
44 |
+ if(! is.null(cols)){ |
|
45 |
+ x <- x[, cols, drop = FALSE] |
|
46 |
+ } |
|
47 |
+ dgCMatrix_colMedians(x, na_rm = na.rm) |
|
44 | 48 |
}) |
45 | 49 |
|
46 |
-#' @rdname colMedians |
|
47 |
-#' @export |
|
48 |
-setMethod("colMedians", signature(x = "dgCMatrix"), |
|
49 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
50 |
- dgCMatrix_colMedians(x, na_rm = na.rm)) |
|
51 | 50 |
|
52 | 51 |
# Vars |
53 | 52 |
|
54 |
-#' @inherit matrixStats::colVars |
|
55 |
-#' @export |
|
56 |
-setGeneric("colVars", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
57 |
- matrixStats::colVars(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
58 |
-}) |
|
59 |
- |
|
60 |
-#' @rdname colVars |
|
53 |
+#' @inherit MatrixGenerics::colVars |
|
61 | 54 |
#' @export |
62 | 55 |
setMethod("colVars", signature(x = "dgCMatrix"), |
63 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
64 |
- dgCMatrix_colVars(x, na_rm = na.rm)) |
|
56 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
57 |
+ if(! is.null(rows)){ |
|
58 |
+ x <- x[rows, , drop = FALSE] |
|
59 |
+ } |
|
60 |
+ if(! is.null(cols)){ |
|
61 |
+ x <- x[, cols, drop = FALSE] |
|
62 |
+ } |
|
63 |
+ dgCMatrix_colVars(x, na_rm = na.rm) |
|
64 |
+}) |
|
65 | 65 |
|
66 | 66 |
|
67 | 67 |
# Sds |
68 | 68 |
|
69 |
-#' @inherit matrixStats::colSds |
|
70 |
-#' @export |
|
71 |
-setGeneric("colSds", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
72 |
- matrixStats::colSds(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
73 |
-}) |
|
74 |
- |
|
75 |
-#' @rdname colSds |
|
69 |
+#' @inherit MatrixGenerics::colSds |
|
76 | 70 |
#' @export |
77 | 71 |
setMethod("colSds", signature(x = "dgCMatrix"), |
78 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
79 |
- sqrt(dgCMatrix_colVars(x, na_rm = na.rm))) |
|
72 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
73 |
+ if(! is.null(rows)){ |
|
74 |
+ x <- x[rows, , drop = FALSE] |
|
75 |
+ } |
|
76 |
+ if(! is.null(cols)){ |
|
77 |
+ x <- x[, cols, drop = FALSE] |
|
78 |
+ } |
|
79 |
+ sqrt(dgCMatrix_colVars(x, na_rm = na.rm)) |
|
80 |
+}) |
|
80 | 81 |
|
81 | 82 |
|
82 | 83 |
# Mads |
... | ... |
@@ -139,32 +140,34 @@ setMethod("colProds", signature(x = "dgCMatrix"), |
139 | 140 |
|
140 | 141 |
# Min |
141 | 142 |
|
142 |
-#' @inherit matrixStats::colMins |
|
143 |
-#' @export |
|
144 |
-setGeneric("colMins", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
145 |
- matrixStats::colMins(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
146 |
-}) |
|
147 |
- |
|
148 |
-#' @rdname colMins |
|
143 |
+#' @inherit MatrixGenerics::colMins |
|
149 | 144 |
#' @export |
150 | 145 |
setMethod("colMins", signature(x = "dgCMatrix"), |
151 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
152 |
- dgCMatrix_colMins(x, na_rm = na.rm)) |
|
146 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
147 |
+ if(! is.null(rows)){ |
|
148 |
+ x <- x[rows, , drop = FALSE] |
|
149 |
+ } |
|
150 |
+ if(! is.null(cols)){ |
|
151 |
+ x <- x[, cols, drop = FALSE] |
|
152 |
+ } |
|
153 |
+ dgCMatrix_colMins(x, na_rm = na.rm) |
|
154 |
+}) |
|
153 | 155 |
|
154 | 156 |
|
155 | 157 |
# Max |
156 | 158 |
|
157 |
-#' @inherit matrixStats::colMaxs |
|
158 |
-#' @export |
|
159 |
-setGeneric("colMaxs", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
160 |
- matrixStats::colMaxs(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
161 |
-}) |
|
162 |
- |
|
163 |
-#' @rdname colMaxs |
|
159 |
+#' @inherit MatrixGenerics::colMaxs |
|
164 | 160 |
#' @export |
165 | 161 |
setMethod("colMaxs", signature(x = "dgCMatrix"), |
166 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
167 |
- dgCMatrix_colMaxs(x, na_rm = na.rm)) |
|
162 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
163 |
+ if(! is.null(rows)){ |
|
164 |
+ x <- x[rows, , drop = FALSE] |
|
165 |
+ } |
|
166 |
+ if(! is.null(cols)){ |
|
167 |
+ x <- x[, cols, drop = FALSE] |
|
168 |
+ } |
|
169 |
+ dgCMatrix_colMaxs(x, na_rm = na.rm) |
|
170 |
+}) |
|
168 | 171 |
|
169 | 172 |
|
170 | 173 |
# OrderStats |
... | ... |
@@ -496,20 +499,20 @@ setMethod("colIQRs", signature(x = "dgCMatrix"), |
496 | 499 |
|
497 | 500 |
# colRanges |
498 | 501 |
|
499 |
-#' @inherit matrixStats::colRanges |
|
500 |
-#' @export |
|
501 |
-setGeneric("colRanges", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
502 |
- matrixStats::colRanges(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
503 |
-}) |
|
504 |
- |
|
505 |
-#' @rdname colRanges |
|
502 |
+#' @inherit MatrixGenerics::colRanges |
|
506 | 503 |
#' @export |
507 | 504 |
setMethod("colRanges", signature(x = "dgCMatrix"), |
508 | 505 |
function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
509 |
- col_max <- colMaxs(x, rows, cols, na.rm = na.rm) |
|
510 |
- col_min <- colMins(x, rows, cols, na.rm = na.rm) |
|
511 |
- unname(cbind(col_min, col_max)) |
|
512 |
- }) |
|
506 |
+ if(! is.null(rows)){ |
|
507 |
+ x <- x[rows, , drop = FALSE] |
|
508 |
+ } |
|
509 |
+ if(! is.null(cols)){ |
|
510 |
+ x <- x[, cols, drop = FALSE] |
|
511 |
+ } |
|
512 |
+ col_max <- colMaxs(x, rows, cols, na.rm = na.rm) |
|
513 |
+ col_min <- colMins(x, rows, cols, na.rm = na.rm) |
|
514 |
+ unname(cbind(col_min, col_max)) |
|
515 |
+}) |
|
513 | 516 |
|
514 | 517 |
|
515 | 518 |
|
... | ... |
@@ -2,77 +2,83 @@ |
2 | 2 |
|
3 | 3 |
# Sum |
4 | 4 |
|
5 |
-#' @rdname colSums2 |
|
6 |
-#' @export |
|
7 |
-setGeneric("rowSums2", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
8 |
- matrixStats::rowSums2(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
9 |
-}) |
|
10 |
- |
|
11 |
-#' @rdname colSums2 |
|
5 |
+#' @rdname colSums2-dgCMatrix-method |
|
12 | 6 |
#' @export |
13 | 7 |
setMethod("rowSums2", signature(x = "dgCMatrix"), |
14 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
15 |
- dgCMatrix_colSums2(t(x), na_rm = na.rm)) |
|
8 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
9 |
+ if(! is.null(rows)){ |
|
10 |
+ x <- x[rows, , drop = FALSE] |
|
11 |
+ } |
|
12 |
+ if(! is.null(cols)){ |
|
13 |
+ x <- x[, cols, drop = FALSE] |
|
14 |
+ } |
|
15 |
+ dgCMatrix_colSums2(t(x), na_rm = na.rm) |
|
16 |
+}) |
|
16 | 17 |
|
17 | 18 |
|
18 | 19 |
|
19 | 20 |
# Mean |
20 | 21 |
|
21 |
-#' @rdname colMeans2 |
|
22 |
-#' @export |
|
23 |
-setGeneric("rowMeans2", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
24 |
- matrixStats::rowMeans2(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
25 |
-}) |
|
26 |
- |
|
27 |
-#' @rdname colMeans2 |
|
22 |
+#' @rdname colMeans2-dgCMatrix-method |
|
28 | 23 |
#' @export |
29 | 24 |
setMethod("rowMeans2", signature(x = "dgCMatrix"), |
30 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
31 |
- dgCMatrix_colMeans2(t(x), na_rm = na.rm)) |
|
25 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
26 |
+ if(! is.null(rows)){ |
|
27 |
+ x <- x[rows, , drop = FALSE] |
|
28 |
+ } |
|
29 |
+ if(! is.null(cols)){ |
|
30 |
+ x <- x[, cols, drop = FALSE] |
|
31 |
+ } |
|
32 |
+ dgCMatrix_colMeans2(t(x), na_rm = na.rm) |
|
33 |
+}) |
|
32 | 34 |
|
33 | 35 |
|
34 | 36 |
# Median |
35 | 37 |
|
36 |
-#' @rdname colMedians |
|
38 |
+#' @rdname colMedians-dgCMatrix-method |
|
37 | 39 |
#' @export |
38 |
-setGeneric("rowMedians", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
39 |
- matrixStats::rowMedians(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
40 |
+setMethod("rowMedians", signature(x = "dgCMatrix"), |
|
41 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
42 |
+ if(! is.null(rows)){ |
|
43 |
+ x <- x[rows, , drop = FALSE] |
|
44 |
+ } |
|
45 |
+ if(! is.null(cols)){ |
|
46 |
+ x <- x[, cols, drop = FALSE] |
|
47 |
+ } |
|
48 |
+ dgCMatrix_colMedians(t(x), na_rm = na.rm) |
|
40 | 49 |
}) |
41 | 50 |
|
42 |
-#' @rdname colMedians |
|
43 |
-#' @export |
|
44 |
-setMethod("rowMedians", signature(x = "dgCMatrix"), |
|
45 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
46 |
- dgCMatrix_colMedians(t(x), na_rm = na.rm)) |
|
47 | 51 |
|
48 | 52 |
# Vars |
49 | 53 |
|
50 |
-#' @rdname colVars |
|
51 |
-#' @export |
|
52 |
-setGeneric("rowVars", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
53 |
- matrixStats::rowVars(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
54 |
-}) |
|
55 |
- |
|
56 |
-#' @rdname colVars |
|
54 |
+#' @rdname colVars-dgCMatrix-method |
|
57 | 55 |
#' @export |
58 | 56 |
setMethod("rowVars", signature(x = "dgCMatrix"), |
59 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
60 |
- dgCMatrix_colVars(t(x), na_rm = na.rm)) |
|
57 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
58 |
+ if(! is.null(rows)){ |
|
59 |
+ x <- x[rows, , drop = FALSE] |
|
60 |
+ } |
|
61 |
+ if(! is.null(cols)){ |
|
62 |
+ x <- x[, cols, drop = FALSE] |
|
63 |
+ } |
|
64 |
+ dgCMatrix_colVars(t(x), na_rm = na.rm) |
|
65 |
+}) |
|
61 | 66 |
|
62 | 67 |
|
63 | 68 |
# Sds |
64 | 69 |
|
65 |
-#' @rdname colSds |
|
66 |
-#' @export |
|
67 |
-setGeneric("rowSds", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
68 |
- matrixStats::rowSds(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
69 |
-}) |
|
70 |
- |
|
71 |
-#' @rdname colSds |
|
70 |
+#' @rdname colSds-dgCMatrix-method |
|
72 | 71 |
#' @export |
73 | 72 |
setMethod("rowSds", signature(x = "dgCMatrix"), |
74 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
75 |
- sqrt(dgCMatrix_colVars(t(x), na_rm = na.rm))) |
|
73 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
74 |
+ if(! is.null(rows)){ |
|
75 |
+ x <- x[rows, , drop = FALSE] |
|
76 |
+ } |
|
77 |
+ if(! is.null(cols)){ |
|
78 |
+ x <- x[, cols, drop = FALSE] |
|
79 |
+ } |
|
80 |
+ sqrt(dgCMatrix_colVars(t(x), na_rm = na.rm)) |
|
81 |
+}) |
|
76 | 82 |
|
77 | 83 |
|
78 | 84 |
|
... | ... |
@@ -124,32 +130,34 @@ setMethod("rowProds", signature(x = "dgCMatrix"), |
124 | 130 |
|
125 | 131 |
# Min |
126 | 132 |
|
127 |
-#' @rdname colMins |
|
128 |
-#' @export |
|
129 |
-setGeneric("rowMins", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
130 |
- matrixStats::rowMins(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
131 |
-}) |
|
132 |
- |
|
133 |
-#' @rdname colMins |
|
133 |
+#' @rdname colMins-dgCMatrix-method |
|
134 | 134 |
#' @export |
135 | 135 |
setMethod("rowMins", signature(x = "dgCMatrix"), |
136 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
137 |
- dgCMatrix_colMins(t(x), na_rm = na.rm)) |
|
136 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
137 |
+ if(! is.null(rows)){ |
|
138 |
+ x <- x[rows, , drop = FALSE] |
|
139 |
+ } |
|
140 |
+ if(! is.null(cols)){ |
|
141 |
+ x <- x[, cols, drop = FALSE] |
|
142 |
+ } |
|
143 |
+ dgCMatrix_colMins(t(x), na_rm = na.rm) |
|
144 |
+}) |
|
138 | 145 |
|
139 | 146 |
|
140 | 147 |
# Max |
141 | 148 |
|
142 |
-#' @rdname colMaxs |
|
143 |
-#' @export |
|
144 |
-setGeneric("rowMaxs", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
145 |
- matrixStats::rowMaxs(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
146 |
-}) |
|
147 |
- |
|
148 |
-#' @rdname colMaxs |
|
149 |
+#' @rdname colMaxs-dgCMatrix-method |
|
149 | 150 |
#' @export |
150 | 151 |
setMethod("rowMaxs", signature(x = "dgCMatrix"), |
151 |
- function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...) |
|
152 |
- dgCMatrix_colMaxs(t(x), na_rm = na.rm)) |
|
152 |
+ function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
153 |
+ if(! is.null(rows)){ |
|
154 |
+ x <- x[rows, , drop = FALSE] |
|
155 |
+ } |
|
156 |
+ if(! is.null(cols)){ |
|
157 |
+ x <- x[, cols, drop = FALSE] |
|
158 |
+ } |
|
159 |
+ dgCMatrix_colMaxs(t(x), na_rm = na.rm) |
|
160 |
+}) |
|
153 | 161 |
|
154 | 162 |
|
155 | 163 |
# OrderStats |
... | ... |
@@ -396,21 +404,21 @@ setMethod("rowIQRs", signature(x = "dgCMatrix"), |
396 | 404 |
|
397 | 405 |
# Ranges |
398 | 406 |
|
399 |
-#' @rdname colRanges |
|
400 |
-#' @export |
|
401 |
-setGeneric("rowRanges", function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
|
402 |
- matrixStats::rowRanges(as.matrix(x), rows = rows, cols = cols, na.rm = na.rm, ...) |
|
403 |
-}) |
|
404 |
- |
|
405 |
-#' @rdname colRanges |
|
407 |
+#' @rdname colRanges-dgCMatrix-method |
|
406 | 408 |
#' @export |
407 | 409 |
setMethod("rowRanges", signature(x = "dgCMatrix"), |
408 | 410 |
function(x, rows = NULL, cols = NULL, na.rm=FALSE, ...){ |
409 |
- tx <- t(x) |
|
410 |
- row_max <- colMaxs(tx, rows, cols, na.rm = na.rm) |
|
411 |
- row_max <- colMins(tx, rows, cols, na.rm = na.rm) |
|
412 |
- unname(cbind(row_max, row_max)) |
|
413 |
- }) |
|
411 |
+ if(! is.null(rows)){ |
|
412 |
+ x <- x[rows, , drop = FALSE] |
|
413 |
+ } |
|
414 |
+ if(! is.null(cols)){ |
|
415 |
+ x <- x[, cols, drop = FALSE] |
|
416 |
+ } |
|
417 |
+ tx <- t(x) |
|
418 |
+ row_max <- colMaxs(tx, rows, cols, na.rm = na.rm) |
|
419 |
+ row_max <- colMins(tx, rows, cols, na.rm = na.rm) |
|
420 |
+ unname(cbind(row_max, row_max)) |
|
421 |
+}) |
|
414 | 422 |
|
415 | 423 |
|
416 | 424 |
|
417 | 425 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,59 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colMaxs,dgCMatrix-method} |
|
5 |
+\alias{colMaxs,dgCMatrix-method} |
|
6 |
+\alias{rowMaxs,dgCMatrix-method} |
|
7 |
+\title{Calculates the maximum for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colMaxs}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowMaxs}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{...}{Additional arguments passed to specific methods.} |
|
28 |
+} |
|
29 |
+\value{ |
|
30 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
31 |
+length N (K). |
|
32 |
+} |
|
33 |
+\description{ |
|
34 |
+Calculates the maximum for each row (column) of a matrix-like object. |
|
35 |
+} |
|
36 |
+\details{ |
|
37 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
38 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowMaxs}} |
|
39 |
+/ \code{matrixStats::\link[matrixStats]{colMaxs}}. |
|
40 |
+} |
|
41 |
+\examples{ |
|
42 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
43 |
+ mat[2, 1] <- NA |
|
44 |
+ mat[3, 3] <- Inf |
|
45 |
+ mat[4, 1] <- 0 |
|
46 |
+ |
|
47 |
+ print(mat) |
|
48 |
+ |
|
49 |
+ rowMaxs(mat) |
|
50 |
+ colMaxs(mat) |
|
51 |
+} |
|
52 |
+\seealso{ |
|
53 |
+\itemize{ |
|
54 |
+\item \code{matrixStats::\link[matrixStats]{rowMaxs}()} and |
|
55 |
+ \code{matrixStats::\link[matrixStats]{colMaxs}()} which are used when |
|
56 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
57 |
+\item For min estimates, see \code{\link{rowMins}()}. |
|
58 |
+} |
|
59 |
+} |
0 | 60 |
deleted file mode 100644 |
... | ... |
@@ -1,50 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colMaxs} |
|
5 |
-\alias{colMaxs} |
|
6 |
-\alias{colMaxs,dgCMatrix-method} |
|
7 |
-\alias{rowMaxs} |
|
8 |
-\alias{rowMaxs,dgCMatrix-method} |
|
9 |
-\title{Gets the range of values in each row (column) of a matrix} |
|
10 |
-\usage{ |
|
11 |
-colMaxs(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colMaxs}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowMaxs(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowMaxs}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Not used.} |
|
36 |
-} |
|
37 |
-\value{ |
|
38 |
-\code{rowRanges()} (\code{colRanges()}) returns a |
|
39 |
-\code{\link[base]{numeric}} Nx2 (Kx2) \code{\link[base]{matrix}}, where N |
|
40 |
-(K) is the number of rows (columns) for which the ranges are calculated. |
|
41 |
- |
|
42 |
-\code{rowMins()/rowMaxs()} (\code{colMins()/colMaxs()}) returns a |
|
43 |
-\code{\link[base]{numeric}} \code{\link[base]{vector}} of length N (K). |
|
44 |
-} |
|
45 |
-\description{ |
|
46 |
-Gets the range of values in each row (column) of a matrix. |
|
47 |
-} |
|
48 |
-\seealso{ |
|
49 |
-\code{\link{rowOrderStats}}() and \code{\link[base]{pmin.int}}(). |
|
50 |
-} |
51 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,61 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colMeans2,dgCMatrix-method} |
|
5 |
+\alias{colMeans2,dgCMatrix-method} |
|
6 |
+\alias{rowMeans2,dgCMatrix-method} |
|
7 |
+\title{Calculates the mean for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colMeans2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowMeans2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{...}{Additional arguments passed to specific methods.} |
|
28 |
+} |
|
29 |
+\value{ |
|
30 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
31 |
+length N (K). |
|
32 |
+} |
|
33 |
+\description{ |
|
34 |
+Calculates the mean for each row (column) of a matrix-like object. |
|
35 |
+} |
|
36 |
+\details{ |
|
37 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
38 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowMeans2}} |
|
39 |
+/ \code{matrixStats::\link[matrixStats]{colMeans2}}. |
|
40 |
+} |
|
41 |
+\examples{ |
|
42 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
43 |
+ mat[2, 1] <- NA |
|
44 |
+ mat[3, 3] <- Inf |
|
45 |
+ mat[4, 1] <- 0 |
|
46 |
+ |
|
47 |
+ print(mat) |
|
48 |
+ |
|
49 |
+ rowMeans2(mat) |
|
50 |
+ colMeans2(mat) |
|
51 |
+} |
|
52 |
+\seealso{ |
|
53 |
+\itemize{ |
|
54 |
+\item \code{matrixStats::\link[matrixStats]{rowMeans2}()} and |
|
55 |
+ \code{matrixStats::\link[matrixStats]{colMeans2}()} which are used when |
|
56 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
57 |
+\item See also \code{\link[base:colSums]{rowMeans}()} for the |
|
58 |
+ corresponding function in base R. |
|
59 |
+\item For variance estimates, see \code{\link{rowVars}()}. |
|
60 |
+} |
|
61 |
+} |
0 | 62 |
deleted file mode 100644 |
... | ... |
@@ -1,48 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colMeans2} |
|
5 |
-\alias{colMeans2} |
|
6 |
-\alias{colMeans2,dgCMatrix-method} |
|
7 |
-\alias{rowMeans2} |
|
8 |
-\alias{rowMeans2,dgCMatrix-method} |
|
9 |
-\title{Calculates the mean for each row (column) in a matrix} |
|
10 |
-\usage{ |
|
11 |
-colMeans2(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colMeans2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowMeans2(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowMeans2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} or a \code{\link[base]{logical}} |
|
23 |
-NxK \code{\link[base]{matrix}}.} |
|
24 |
- |
|
25 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
26 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
27 |
-is done.} |
|
28 |
- |
|
29 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
30 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
31 |
-is done.} |
|
32 |
- |
|
33 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
34 |
-are excluded first, otherwise not.} |
|
35 |
- |
|
36 |
-\item{...}{Not used.} |
|
37 |
-} |
|
38 |
-\value{ |
|
39 |
-Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
40 |
-length N (K). |
|
41 |
-} |
|
42 |
-\description{ |
|
43 |
-Calculates the mean for each row (column) in a matrix. |
|
44 |
-} |
|
45 |
-\details{ |
|
46 |
-The implementation of \code{rowMeans2()} and \code{colMeans2()} is |
|
47 |
-optimized for both speed and memory. |
|
48 |
-} |
49 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,60 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colMedians,dgCMatrix-method} |
|
5 |
+\alias{colMedians,dgCMatrix-method} |
|
6 |
+\alias{rowMedians,dgCMatrix-method} |
|
7 |
+\title{Calculates the median for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colMedians}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowMedians}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{...}{Additional arguments passed to specific methods.} |
|
28 |
+} |
|
29 |
+\value{ |
|
30 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
31 |
+length N (K). |
|
32 |
+} |
|
33 |
+\description{ |
|
34 |
+Calculates the median for each row (column) of a matrix-like object. |
|
35 |
+} |
|
36 |
+\details{ |
|
37 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
38 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowMedians}} |
|
39 |
+/ \code{matrixStats::\link[matrixStats]{colMedians}}. |
|
40 |
+} |
|
41 |
+\examples{ |
|
42 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
43 |
+ mat[2, 1] <- NA |
|
44 |
+ mat[3, 3] <- Inf |
|
45 |
+ mat[4, 1] <- 0 |
|
46 |
+ |
|
47 |
+ print(mat) |
|
48 |
+ |
|
49 |
+ rowMedians(mat) |
|
50 |
+ colMedians(mat) |
|
51 |
+} |
|
52 |
+\seealso{ |
|
53 |
+\itemize{ |
|
54 |
+\item \code{matrixStats::\link[matrixStats]{rowMedians}()} and |
|
55 |
+ \code{matrixStats::\link[matrixStats]{colMedians}()} which are used when |
|
56 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
57 |
+\item For mean estimates, see \code{\link{rowMeans2}()} and |
|
58 |
+ \code{\link[base:colSums]{rowMeans}()}. |
|
59 |
+} |
|
60 |
+} |
0 | 61 |
deleted file mode 100644 |
... | ... |
@@ -1,59 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colMedians} |
|
5 |
-\alias{colMedians} |
|
6 |
-\alias{colMedians,dgCMatrix-method} |
|
7 |
-\alias{rowMedians} |
|
8 |
-\alias{rowMedians,dgCMatrix-method} |
|
9 |
-\title{Calculates the median for each row (column) in a matrix} |
|
10 |
-\usage{ |
|
11 |
-colMedians(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colMedians}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowMedians(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowMedians}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Not used.} |
|
36 |
-} |
|
37 |
-\value{ |
|
38 |
-Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
39 |
-length N (K). |
|
40 |
-} |
|
41 |
-\description{ |
|
42 |
-Calculates the median for each row (column) in a matrix. |
|
43 |
-} |
|
44 |
-\details{ |
|
45 |
-The implementation of \code{rowMedians()} and \code{colMedians()} is |
|
46 |
-optimized for both speed and memory. To avoid coercing to |
|
47 |
-\code{\link[base]{double}}s (and hence memory allocation), there is a |
|
48 |
-special implementation for \code{\link[base]{integer}} matrices. That is, |
|
49 |
-if \code{x} is an \code{\link[base]{integer}} \code{\link[base]{matrix}}, |
|
50 |
-then \code{rowMedians(as.double(x))} (\code{rowMedians(as.double(x))}) would |
|
51 |
-require three times the memory of \code{rowMedians(x)} |
|
52 |
-(\code{colMedians(x)}), but all this is avoided. |
|
53 |
-} |
|
54 |
-\seealso{ |
|
55 |
-See \code{\link{rowWeightedMedians}()} and |
|
56 |
-\code{colWeightedMedians()} for weighted medians. |
|
57 |
-For mean estimates, see \code{\link{rowMeans2}()} and |
|
58 |
-\code{\link[base:colSums]{rowMeans}()}. |
|
59 |
-} |
60 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,59 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colMins,dgCMatrix-method} |
|
5 |
+\alias{colMins,dgCMatrix-method} |
|
6 |
+\alias{rowMins,dgCMatrix-method} |
|
7 |
+\title{Calculates the minimum for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colMins}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowMins}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{...}{Additional arguments passed to specific methods.} |
|
28 |
+} |
|
29 |
+\value{ |
|
30 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
31 |
+length N (K). |
|
32 |
+} |
|
33 |
+\description{ |
|
34 |
+Calculates the minimum for each row (column) of a matrix-like object. |
|
35 |
+} |
|
36 |
+\details{ |
|
37 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
38 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowMins}} |
|
39 |
+/ \code{matrixStats::\link[matrixStats]{colMins}}. |
|
40 |
+} |
|
41 |
+\examples{ |
|
42 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
43 |
+ mat[2, 1] <- NA |
|
44 |
+ mat[3, 3] <- Inf |
|
45 |
+ mat[4, 1] <- 0 |
|
46 |
+ |
|
47 |
+ print(mat) |
|
48 |
+ |
|
49 |
+ rowMins(mat) |
|
50 |
+ colMins(mat) |
|
51 |
+} |
|
52 |
+\seealso{ |
|
53 |
+\itemize{ |
|
54 |
+\item \code{matrixStats::\link[matrixStats]{rowMins}()} and |
|
55 |
+ \code{matrixStats::\link[matrixStats]{colMins}()} which are used when |
|
56 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
57 |
+\item For max estimates, see \code{\link{rowMaxs}()}. |
|
58 |
+} |
|
59 |
+} |
0 | 60 |
deleted file mode 100644 |
... | ... |
@@ -1,50 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colMins} |
|
5 |
-\alias{colMins} |
|
6 |
-\alias{colMins,dgCMatrix-method} |
|
7 |
-\alias{rowMins} |
|
8 |
-\alias{rowMins,dgCMatrix-method} |
|
9 |
-\title{Gets the range of values in each row (column) of a matrix} |
|
10 |
-\usage{ |
|
11 |
-colMins(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colMins}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowMins(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowMins}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Not used.} |
|
36 |
-} |
|
37 |
-\value{ |
|
38 |
-\code{rowRanges()} (\code{colRanges()}) returns a |
|
39 |
-\code{\link[base]{numeric}} Nx2 (Kx2) \code{\link[base]{matrix}}, where N |
|
40 |
-(K) is the number of rows (columns) for which the ranges are calculated. |
|
41 |
- |
|
42 |
-\code{rowMins()/rowMaxs()} (\code{colMins()/colMaxs()}) returns a |
|
43 |
-\code{\link[base]{numeric}} \code{\link[base]{vector}} of length N (K). |
|
44 |
-} |
|
45 |
-\description{ |
|
46 |
-Gets the range of values in each row (column) of a matrix. |
|
47 |
-} |
|
48 |
-\seealso{ |
|
49 |
-\code{\link{rowOrderStats}}() and \code{\link[base]{pmin.int}}(). |
|
50 |
-} |
51 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,60 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colRanges,dgCMatrix-method} |
|
5 |
+\alias{colRanges,dgCMatrix-method} |
|
6 |
+\alias{rowRanges,dgCMatrix-method} |
|
7 |
+\title{Calculates the mininum and maximum for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colRanges}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowRanges}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{...}{Additional arguments passed to specific methods.} |
|
28 |
+} |
|
29 |
+\value{ |
|
30 |
+a \code{\link[base]{numeric}} \code{Nx2} (\code{Kx2}) \code{\link{matrix}}, where |
|
31 |
+ N (K) is the number of rows (columns) for which the ranges are calculated. |
|
32 |
+} |
|
33 |
+\description{ |
|
34 |
+Calculates the mininum and maximum for each row (column) of a matrix-like object. |
|
35 |
+} |
|
36 |
+\details{ |
|
37 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
38 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowRanges}} |
|
39 |
+/ \code{matrixStats::\link[matrixStats]{colRanges}}. |
|
40 |
+} |
|
41 |
+\examples{ |
|
42 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
43 |
+ mat[2, 1] <- NA |
|
44 |
+ mat[3, 3] <- Inf |
|
45 |
+ mat[4, 1] <- 0 |
|
46 |
+ |
|
47 |
+ print(mat) |
|
48 |
+ |
|
49 |
+ rowRanges(mat) |
|
50 |
+ colRanges(mat) |
|
51 |
+} |
|
52 |
+\seealso{ |
|
53 |
+\itemize{ |
|
54 |
+\item \code{matrixStats::\link[matrixStats]{rowRanges}()} and |
|
55 |
+ \code{matrixStats::\link[matrixStats]{colRanges}()} which are used when |
|
56 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
57 |
+\item For max estimates, see \code{\link{rowMaxs}()}. |
|
58 |
+\item For min estimates, see \code{\link{rowMins}()}. |
|
59 |
+} |
|
60 |
+} |
0 | 61 |
deleted file mode 100644 |
... | ... |
@@ -1,50 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colRanges} |
|
5 |
-\alias{colRanges} |
|
6 |
-\alias{colRanges,dgCMatrix-method} |
|
7 |
-\alias{rowRanges} |
|
8 |
-\alias{rowRanges,dgCMatrix-method} |
|
9 |
-\title{Gets the range of values in each row (column) of a matrix} |
|
10 |
-\usage{ |
|
11 |
-colRanges(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colRanges}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowRanges(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowRanges}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Not used.} |
|
36 |
-} |
|
37 |
-\value{ |
|
38 |
-\code{rowRanges()} (\code{colRanges()}) returns a |
|
39 |
-\code{\link[base]{numeric}} Nx2 (Kx2) \code{\link[base]{matrix}}, where N |
|
40 |
-(K) is the number of rows (columns) for which the ranges are calculated. |
|
41 |
- |
|
42 |
-\code{rowMins()/rowMaxs()} (\code{colMins()/colMaxs()}) returns a |
|
43 |
-\code{\link[base]{numeric}} \code{\link[base]{vector}} of length N (K). |
|
44 |
-} |
|
45 |
-\description{ |
|
46 |
-Gets the range of values in each row (column) of a matrix. |
|
47 |
-} |
|
48 |
-\seealso{ |
|
49 |
-\code{\link{rowOrderStats}}() and \code{\link[base]{pmin.int}}(). |
|
50 |
-} |
51 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,63 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colSds,dgCMatrix-method} |
|
5 |
+\alias{colSds,dgCMatrix-method} |
|
6 |
+\alias{rowSds,dgCMatrix-method} |
|
7 |
+\title{Calculates the standard deviation for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colSds}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, center = NULL, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowSds}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{center}{(optional) the center, defaults to the row means} |
|
28 |
+ |
|
29 |
+\item{...}{Additional arguments passed to specific methods.} |
|
30 |
+} |
|
31 |
+\value{ |
|
32 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
33 |
+length N (K). |
|
34 |
+} |
|
35 |
+\description{ |
|
36 |
+Calculates the standard deviation for each row (column) of a matrix-like object. |
|
37 |
+} |
|
38 |
+\details{ |
|
39 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
40 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowSds}} |
|
41 |
+/ \code{matrixStats::\link[matrixStats]{colSds}}. |
|
42 |
+} |
|
43 |
+\examples{ |
|
44 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
45 |
+ mat[2, 1] <- NA |
|
46 |
+ mat[3, 3] <- Inf |
|
47 |
+ mat[4, 1] <- 0 |
|
48 |
+ |
|
49 |
+ print(mat) |
|
50 |
+ |
|
51 |
+ rowSds(mat) |
|
52 |
+ colSds(mat) |
|
53 |
+} |
|
54 |
+\seealso{ |
|
55 |
+\itemize{ |
|
56 |
+\item \code{matrixStats::\link[matrixStats]{rowSds}()} and |
|
57 |
+ \code{matrixStats::\link[matrixStats]{colSds}()} which are used when |
|
58 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
59 |
+\item For mean estimates, see \code{\link{rowMeans2}()} and |
|
60 |
+ \code{\link[base:colSums]{rowMeans}()}. |
|
61 |
+\item For variance estimates, see \code{\link{rowVars}()}. |
|
62 |
+} |
|
63 |
+} |
0 | 64 |
deleted file mode 100644 |
... | ... |
@@ -1,48 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colSds} |
|
5 |
-\alias{colSds} |
|
6 |
-\alias{colSds,dgCMatrix-method} |
|
7 |
-\alias{rowSds} |
|
8 |
-\alias{rowSds,dgCMatrix-method} |
|
9 |
-\title{Standard deviation estimates for each row (column) in a matrix} |
|
10 |
-\usage{ |
|
11 |
-colSds(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colSds}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowSds(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowSds}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Additional arguments passed to \code{rowMeans()} and |
|
36 |
-\code{rowSums()}.} |
|
37 |
-} |
|
38 |
-\value{ |
|
39 |
-Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
40 |
-length N (K). |
|
41 |
-} |
|
42 |
-\description{ |
|
43 |
-Standard deviation estimates for each row (column) in a matrix. |
|
44 |
-} |
|
45 |
-\seealso{ |
|
46 |
-\code{\link[stats]{sd}}, \code{\link[stats]{mad}} and |
|
47 |
-\code{\link[stats:cor]{var}}. \code{\link{rowIQRs}}(). |
|
48 |
-} |
... | ... |
@@ -1,12 +1,16 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 |
-% Please edit documentation in R/methods.R |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 | 3 |
\docType{methods} |
4 | 4 |
\name{colSums2,dgCMatrix-method} |
5 | 5 |
\alias{colSums2,dgCMatrix-method} |
6 |
+\alias{rowSums2,dgCMatrix-method} |
|
6 | 7 |
\title{Calculates the sum for each row (column) of a matrix-like object} |
7 | 8 |
\usage{ |
8 | 9 |
\S4method{colSums2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
9 | 10 |
na.rm = FALSE, ...) |
11 |
+ |
|
12 |
+\S4method{rowSums2}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
10 | 14 |
} |
11 | 15 |
\arguments{ |
12 | 16 |
\item{x}{An NxK matrix-like object.} |
13 | 17 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,63 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
+\docType{methods} |
|
4 |
+\name{colVars,dgCMatrix-method} |
|
5 |
+\alias{colVars,dgCMatrix-method} |
|
6 |
+\alias{rowVars,dgCMatrix-method} |
|
7 |
+\title{Calculates the variance for each row (column) of a matrix-like object} |
|
8 |
+\usage{ |
|
9 |
+\S4method{colVars}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
10 |
+ na.rm = FALSE, center = NULL, ...) |
|
11 |
+ |
|
12 |
+\S4method{rowVars}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
13 |
+ na.rm = FALSE, ...) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{An NxK matrix-like object.} |
|
17 |
+ |
|
18 |
+\item{rows}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
19 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
20 |
+ |
|
21 |
+\item{cols}{A \code{\link[base]{vector}} indicating the subset (and/or |
|
22 |
+columns) to operate over. If \code{\link[base]{NULL}}, no subsetting is done.} |
|
23 |
+ |
|
24 |
+\item{na.rm}{If \code{\link[base:logical]{TRUE}}, \code{\link[base]{NA}}s |
|
25 |
+are excluded first, otherwise not.} |
|
26 |
+ |
|
27 |
+\item{center}{(optional) the center, defaults to the row means} |
|
28 |
+ |
|
29 |
+\item{...}{Additional arguments passed to specific methods.} |
|
30 |
+} |
|
31 |
+\value{ |
|
32 |
+Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
33 |
+length N (K). |
|
34 |
+} |
|
35 |
+\description{ |
|
36 |
+Calculates the variance for each row (column) of a matrix-like object. |
|
37 |
+} |
|
38 |
+\details{ |
|
39 |
+The S4 methods for \code{x} of type \code{\link[base]{matrix}} or |
|
40 |
+\code{\link[base]{numeric}} call \code{matrixStats::\link[matrixStats]{rowVars}} |
|
41 |
+/ \code{matrixStats::\link[matrixStats]{colVars}}. |
|
42 |
+} |
|
43 |
+\examples{ |
|
44 |
+mat <- matrix(rnorm(15), nrow = 5, ncol = 3) |
|
45 |
+ mat[2, 1] <- NA |
|
46 |
+ mat[3, 3] <- Inf |
|
47 |
+ mat[4, 1] <- 0 |
|
48 |
+ |
|
49 |
+ print(mat) |
|
50 |
+ |
|
51 |
+ rowVars(mat) |
|
52 |
+ colVars(mat) |
|
53 |
+} |
|
54 |
+\seealso{ |
|
55 |
+\itemize{ |
|
56 |
+\item \code{matrixStats::\link[matrixStats]{rowVars}()} and |
|
57 |
+ \code{matrixStats::\link[matrixStats]{colVars}()} which are used when |
|
58 |
+ the input is a \code{matrix} or \code{numeric} vector. |
|
59 |
+\item For mean estimates, see \code{\link{rowMeans2}()} and |
|
60 |
+ \code{\link[base:colSums]{rowMeans}()}. |
|
61 |
+\item For standard deviation estimates, see \code{\link{rowSds}()}. |
|
62 |
+} |
|
63 |
+} |
0 | 64 |
deleted file mode 100644 |
... | ... |
@@ -1,101 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/methods.R, R/methods_row.R |
|
3 |
-\docType{methods} |
|
4 |
-\name{colVars} |
|
5 |
-\alias{colVars} |
|
6 |
-\alias{colVars,dgCMatrix-method} |
|
7 |
-\alias{rowVars} |
|
8 |
-\alias{rowVars,dgCMatrix-method} |
|
9 |
-\title{Variance estimates for each row (column) in a matrix} |
|
10 |
-\usage{ |
|
11 |
-colVars(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
12 |
- |
|
13 |
-\S4method{colVars}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
14 |
- na.rm = FALSE, ...) |
|
15 |
- |
|
16 |
-rowVars(x, rows = NULL, cols = NULL, na.rm = FALSE, ...) |
|
17 |
- |
|
18 |
-\S4method{rowVars}{dgCMatrix}(x, rows = NULL, cols = NULL, |
|
19 |
- na.rm = FALSE, ...) |
|
20 |
-} |
|
21 |
-\arguments{ |
|
22 |
-\item{x}{A \code{\link[base]{numeric}} NxK \code{\link[base]{matrix}}.} |
|
23 |
- |
|
24 |
-\item{rows}{A \code{\link[base]{vector}} indicating subset of rows |
|
25 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
26 |
-is done.} |
|
27 |
- |
|
28 |
-\item{cols}{A \code{\link[base]{vector}} indicating subset of rows |
|
29 |
-(and/or columns) to operate over. If \code{\link[base]{NULL}}, no subsetting |
|
30 |
-is done.} |
|
31 |
- |
|
32 |
-\item{na.rm}{If \code{\link[base:logical]{TRUE}}, missing values |
|
33 |
-are excluded first, otherwise not.} |
|
34 |
- |
|
35 |
-\item{...}{Additional arguments passed to \code{rowMeans()} and |
|
36 |
-\code{rowSums()}.} |
|
37 |
-} |
|
38 |
-\value{ |
|
39 |
-Returns a \code{\link[base]{numeric}} \code{\link[base]{vector}} of |
|
40 |
-length N (K). |
|
41 |
-} |
|
42 |
-\description{ |
|
43 |
-Variance estimates for each row (column) in a matrix. |
|
44 |
-} |
|
45 |
-\examples{ |
|
46 |
-set.seed(1) |
|
47 |
- |
|
48 |
-x <- matrix(rnorm(20), nrow = 5, ncol = 4) |
|
49 |
-print(x) |
|
50 |
- |
|
51 |
-# Row averages |
|
52 |
-print(rowMeans(x)) |
|
53 |
-print(rowMedians(x)) |
|
54 |
- |
|
55 |
-# Column averages |
|
56 |
-print(colMeans(x)) |
|
57 |
-print(colMedians(x)) |
|
58 |
- |
|
59 |
- |
|
60 |
-# Row variabilities |
|
61 |
-print(rowVars(x)) |
|
62 |
-print(rowSds(x)) |
|
63 |
-print(rowMads(x)) |
|
64 |
-print(rowIQRs(x)) |
|
65 |
- |
|
66 |
-# Column variabilities |
|
67 |
-print(rowVars(x)) |
|
68 |
-print(colSds(x)) |
|
69 |
-print(colMads(x)) |
|
70 |
-print(colIQRs(x)) |
|
71 |
- |
|
72 |
- |
|
73 |
-# Row ranges |
|
74 |
-print(rowRanges(x)) |
|
75 |
-print(cbind(rowMins(x), rowMaxs(x))) |
|
76 |
-print(cbind(rowOrderStats(x, which = 1), rowOrderStats(x, which = ncol(x)))) |
|
77 |
- |
|
78 |
-# Column ranges |
|
79 |
-print(colRanges(x)) |
|
80 |
-print(cbind(colMins(x), colMaxs(x))) |
|
81 |
-print(cbind(colOrderStats(x, which = 1), colOrderStats(x, which = nrow(x)))) |
|
82 |
- |
|
83 |
- |
|
84 |
-x <- matrix(rnorm(2400), nrow = 50, ncol = 40) |
|
85 |
- |
|
86 |
-# Row standard deviations |
|
87 |
-d <- rowDiffs(x) |
|
88 |
-s1 <- rowSds(d) / sqrt(2) |
|
89 |
-s2 <- rowSds(x) |
|
90 |
-print(summary(s1 - s2)) |
|
91 |
- |
|
92 |
-# Column standard deviations |
|
93 |
-d <- colDiffs(x) |
|
94 |
-s1 <- colSds(d) / sqrt(2) |
|
95 |
-s2 <- colSds(x) |
|
96 |
-print(summary(s1 - s2)) |
|
97 |
-} |
|
98 |
-\seealso{ |
|
99 |
-See \code{rowMeans()} and \code{rowSums()} in |
|
100 |
-\code{\link[base]{colSums}}(). |
|
101 |
-} |