... | ... |
@@ -64,6 +64,7 @@ export(retrieveFeatureIndex) |
64 | 64 |
export(runParams) |
65 | 65 |
export(sampleLabel) |
66 | 66 |
export(selectBestModel) |
67 |
+export(selectFeatures) |
|
67 | 68 |
export(simulateCells) |
68 | 69 |
export(simulateContamination) |
69 | 70 |
export(splitModule) |
... | ... |
@@ -116,6 +117,7 @@ exportMethods(resamplePerplexity) |
116 | 117 |
exportMethods(runParams) |
117 | 118 |
exportMethods(sampleLabel) |
118 | 119 |
exportMethods(selectBestModel) |
120 |
+exportMethods(selectFeatures) |
|
119 | 121 |
exportMethods(splitModule) |
120 | 122 |
exportMethods(subsetCeldaList) |
121 | 123 |
import(Rcpp) |
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
#' @title Get or set the cell cluster labels from a celda |
2 |
-#' \linkS4class{SingleCellExperiment} object or celda model |
|
2 |
+#' \linkS4class{SingleCellExperiment} object or celda model |
|
3 | 3 |
#' object. |
4 | 4 |
#' @description Return or set the cell cluster labels determined |
5 | 5 |
#' by \link{celda_C} or \link{celda_CG} models. |
... | ... |
@@ -7,9 +7,12 @@ |
7 | 7 |
#' \itemize{ |
8 | 8 |
#' \item A \linkS4class{SingleCellExperiment} object returned by |
9 | 9 |
#' \link{celda_C}, or \link{celda_CG}, with the matrix |
10 |
-#' located in the \code{useAssay} assay slot. |
|
11 |
-#' Rows represent features and columns represent cells. |
|
10 |
+#' located in the \code{useAssay} assay slot. The |
|
11 |
+#' a \link[SingleCellExperiment]{altExp} slot with name \code{altExpName} will |
|
12 |
+#' be used. Rows represent features and columns represent cells. |
|
12 | 13 |
#' \item Celda model object.} |
14 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
15 |
+#' to use. Default "featureSubset". |
|
13 | 16 |
#' @param value Character vector of cell cluster labels for replacements. Works |
14 | 17 |
#' only if \code{x} is a \linkS4class{SingleCellExperiment} object. |
15 | 18 |
#' @return One of |
... | ... |
@@ -22,7 +25,7 @@ |
22 | 25 |
#' Models) and/or feature module labels (for celda_G and celdaCG Models).} |
23 | 26 |
#' @export |
24 | 27 |
setGeneric("celdaClusters", |
25 |
- function(x) { |
|
28 |
+ function(x, ...) { |
|
26 | 29 |
standardGeneric("celdaClusters") |
27 | 30 |
}) |
28 | 31 |
|
... | ... |
@@ -34,8 +37,9 @@ setGeneric("celdaClusters", |
34 | 37 |
#' @export |
35 | 38 |
setMethod("celdaClusters", |
36 | 39 |
signature(x = "SingleCellExperiment"), |
37 |
- function(x) { |
|
38 |
- return(SummarizedExperiment::colData(x)$celda_cell_cluster) |
|
40 |
+ function(x, altExpName = "featureSubset") { |
|
41 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
42 |
+ return(SummarizedExperiment::colData(altExp)$celda_cell_cluster) |
|
39 | 43 |
}) |
40 | 44 |
|
41 | 45 |
|
... | ... |
@@ -55,34 +59,38 @@ setMethod("celdaClusters", |
55 | 59 |
#' @rdname celdaClusters |
56 | 60 |
#' @export |
57 | 61 |
setGeneric("celdaClusters<-", |
58 |
- function(x, value) standardGeneric("celdaClusters<-") |
|
62 |
+ function(x, ...) standardGeneric("celdaClusters<-") |
|
59 | 63 |
) |
60 | 64 |
|
61 | 65 |
|
62 | 66 |
#' @rdname celdaClusters |
63 | 67 |
#' @export |
64 | 68 |
setReplaceMethod("celdaClusters", signature(x = "SingleCellExperiment"), |
65 |
- function(x, value) { |
|
66 |
- SummarizedExperiment::colData(x)$celda_cell_cluster <- value |
|
69 |
+ function(x, altExpName = "featureSubset", value) { |
|
70 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
71 |
+ SummarizedExperiment::colData(altExp)$celda_cell_cluster <- value |
|
72 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
67 | 73 |
return(x) |
68 | 74 |
}) |
69 | 75 |
|
70 | 76 |
|
71 | 77 |
#' @title Get or set the feature module labels from a celda |
72 |
-#' \linkS4class{SingleCellExperiment} object. |
|
78 |
+#' \linkS4class{SingleCellExperiment} object. |
|
73 | 79 |
#' @description Return or set the feature module cluster labels determined |
74 | 80 |
#' by \link{celda_G} or \link{celda_CG} models. |
75 | 81 |
#' @param sce A \linkS4class{SingleCellExperiment} object returned by |
76 | 82 |
#' \link{celda_G}, or \link{celda_CG}, with the matrix |
77 | 83 |
#' located in the \code{useAssay} assay slot. |
78 | 84 |
#' Rows represent features and columns represent cells. |
85 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
86 |
+#' to use. Default "featureSubset". |
|
79 | 87 |
#' @param value Character vector of feature module labels for replacements. |
80 | 88 |
#' Works only if \code{x} is a \linkS4class{SingleCellExperiment} object. |
81 | 89 |
#' @return Character vector. Contains feature module labels for each |
82 | 90 |
#' feature in x. |
83 | 91 |
#' @export |
84 | 92 |
setGeneric("celdaModules", |
85 |
- function(sce) { |
|
93 |
+ function(sce, ...) { |
|
86 | 94 |
standardGeneric("celdaModules") |
87 | 95 |
}) |
88 | 96 |
|
... | ... |
@@ -94,23 +102,26 @@ setGeneric("celdaModules", |
94 | 102 |
#' @export |
95 | 103 |
setMethod("celdaModules", |
96 | 104 |
signature(sce = "SingleCellExperiment"), |
97 |
- function(sce) { |
|
98 |
- return(SummarizedExperiment::rowData(sce)$celda_feature_module) |
|
105 |
+ function(sce, altExpName = "featureSubset") { |
|
106 |
+ altExp <- SingleCellExperiment::altExp(sce, altExpName) |
|
107 |
+ return(SummarizedExperiment::rowData(altExp)$celda_feature_module) |
|
99 | 108 |
}) |
100 | 109 |
|
101 | 110 |
|
102 | 111 |
#' @rdname celdaModules |
103 | 112 |
#' @export |
104 | 113 |
setGeneric("celdaModules<-", |
105 |
- function(sce, value) standardGeneric("celdaModules<-") |
|
114 |
+ function(sce, ...) standardGeneric("celdaModules<-") |
|
106 | 115 |
) |
107 | 116 |
|
108 | 117 |
|
109 | 118 |
#' @rdname celdaModules |
110 | 119 |
#' @export |
111 | 120 |
setReplaceMethod("celdaModules", signature(sce = "SingleCellExperiment"), |
112 |
- function(sce, value) { |
|
121 |
+ function(sce, altExpName = "featureSubset", value) { |
|
122 |
+ altExp <- SingleCellExperiment::altExp(sce, altExpName) |
|
113 | 123 |
SummarizedExperiment::rowData(sce)$celda_feature_module <- value |
124 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
114 | 125 |
return(sce) |
115 | 126 |
}) |
116 | 127 |
|
... | ... |
@@ -125,13 +136,15 @@ setReplaceMethod("celdaModules", signature(sce = "SingleCellExperiment"), |
125 | 136 |
#' located in the \code{useAssay} assay slot. |
126 | 137 |
#' Rows represent features and columns represent cells. |
127 | 138 |
#' \item A celda model object.} |
139 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
140 |
+#' to use. Default "featureSubset". |
|
128 | 141 |
#' @param value Character vector of sample labels for replacements. Works |
129 | 142 |
#' only is \code{x} is a \linkS4class{SingleCellExperiment} object. |
130 | 143 |
#' @return Character vector. Contains the sample labels provided at model |
131 | 144 |
#' creation, or those automatically generated by celda. |
132 | 145 |
#' @export |
133 | 146 |
setGeneric("sampleLabel", |
134 |
- function(x) { |
|
147 |
+ function(x, ...) { |
|
135 | 148 |
standardGeneric("sampleLabel") |
136 | 149 |
}) |
137 | 150 |
|
... | ... |
@@ -143,21 +156,24 @@ setGeneric("sampleLabel", |
143 | 156 |
#' @export |
144 | 157 |
setMethod("sampleLabel", |
145 | 158 |
signature(x = "SingleCellExperiment"), |
146 |
- function(x) { |
|
147 |
- return(SummarizedExperiment::colData(x)$celda_sample_label) |
|
159 |
+ function(x, altExpName = "featureSubset") { |
|
160 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
161 |
+ return(SummarizedExperiment::colData(altExp)$celda_sample_label) |
|
148 | 162 |
}) |
149 | 163 |
|
150 | 164 |
|
151 | 165 |
#' @rdname sampleLabel |
152 | 166 |
#' @export |
153 | 167 |
setGeneric("sampleLabel<-", |
154 |
- function(x, value) standardGeneric("sampleLabel<-") |
|
168 |
+ function(x, ...) standardGeneric("sampleLabel<-") |
|
155 | 169 |
) |
156 | 170 |
#' @rdname sampleLabel |
157 | 171 |
#' @export |
158 | 172 |
setReplaceMethod("sampleLabel", signature(x = "SingleCellExperiment"), |
159 |
- function(x, value) { |
|
160 |
- SummarizedExperiment::colData(x)$celda_sample_label <- value |
|
173 |
+ function(x, altExpName = "featureSubset", value) { |
|
174 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
175 |
+ SummarizedExperiment::colData(altExp)$celda_sample_label <- value |
|
176 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
161 | 177 |
return(x) |
162 | 178 |
}) |
163 | 179 |
|
... | ... |
@@ -238,13 +254,14 @@ setMethod("matrixNames", |
238 | 254 |
#' priors from the celdaList object when it was created. |
239 | 255 |
#' @param x An object of class \linkS4class{SingleCellExperiment} or class |
240 | 256 |
#' \code{celdaList}. |
257 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
258 |
+#' to use. Default "featureSubset". |
|
241 | 259 |
#' @return Data Frame. Contains details on the various K/L parameters, chain |
242 | 260 |
#' parameters, seed, and final log-likelihoods derived for each model in the |
243 | 261 |
#' provided celdaList. |
244 | 262 |
#' @export |
245 |
-setGeneric( |
|
246 |
- "runParams", |
|
247 |
- function(x) { |
|
263 |
+setGeneric("runParams", |
|
264 |
+ function(x, ...) { |
|
248 | 265 |
standardGeneric("runParams") |
249 | 266 |
} |
250 | 267 |
) |
... | ... |
@@ -257,8 +274,9 @@ setGeneric( |
257 | 274 |
#' @export |
258 | 275 |
setMethod("runParams", |
259 | 276 |
signature(x = "SingleCellExperiment"), |
260 |
- function(x) { |
|
261 |
- return(x@metadata$celda_grid_search@runParams) |
|
277 |
+ function(x, altExpName = "featureSubset") { |
|
278 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
279 |
+ return(altExp@metadata$celda_grid_search@runParams) |
|
262 | 280 |
} |
263 | 281 |
) |
264 | 282 |
|
... | ... |
@@ -282,12 +300,14 @@ setMethod("runParams", |
282 | 300 |
#' \link{celdaGridSearch} run. |
283 | 301 |
#' @param x An object of class \linkS4class{SingleCellExperiment} or |
284 | 302 |
#' \code{celdaList}. |
303 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
304 |
+#' to use. Default "featureSubset". |
|
285 | 305 |
#' @return List. Contains one celdaModel object for each of the parameters |
286 | 306 |
#' specified in \code{runParams(x)}. |
287 | 307 |
#' @export |
288 | 308 |
setGeneric( |
289 | 309 |
"resList", |
290 |
- function(x) { |
|
310 |
+ function(x, ...) { |
|
291 | 311 |
standardGeneric("resList") |
292 | 312 |
} |
293 | 313 |
) |
... | ... |
@@ -300,8 +320,9 @@ setGeneric( |
300 | 320 |
#' @export |
301 | 321 |
setMethod("resList", |
302 | 322 |
signature(x = "SingleCellExperiment"), |
303 |
- function(x) { |
|
304 |
- return(x@metadata$celda_grid_search@resList) |
|
323 |
+ function(x, altExpName = "featureSubset") { |
|
324 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
325 |
+ return(altExp@metadata$celda_grid_search@resList) |
|
305 | 326 |
} |
306 | 327 |
) |
307 | 328 |
|
... | ... |
@@ -317,3 +338,121 @@ setMethod("resList", |
317 | 338 |
return(x@resList) |
318 | 339 |
} |
319 | 340 |
) |
341 |
+ |
|
342 |
+ |
|
343 |
+#' @title Get celda model from a celda |
|
344 |
+#' \link[SingleCellExperiment]{SingleCellExperiment} object |
|
345 |
+#' @description Return the celda model for \code{sce} returned by |
|
346 |
+#' \link{celda_C}, \link{celda_G} or \link{celda_CG}. |
|
347 |
+#' @param sce A \link[SingleCellExperiment]{SingleCellExperiment} object |
|
348 |
+#' returned by \link{celda_C}, \link{celda_G}, or \link{celda_CG}. |
|
349 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
350 |
+#' to use. Default "featureSubset". |
|
351 |
+#' @return Character. The celda model. Can be one of "celda_C", "celda_G", or |
|
352 |
+#' "celda_CG". |
|
353 |
+#' @examples |
|
354 |
+#' data(sceCeldaCG) |
|
355 |
+#' celdaModel(sceCeldaCG) |
|
356 |
+#' @export |
|
357 |
+setGeneric("celdaModel", |
|
358 |
+ function(sce, ...) { |
|
359 |
+ standardGeneric("celdaModel") |
|
360 |
+ }) |
|
361 |
+#' @rdname celdaModel |
|
362 |
+#' @export |
|
363 |
+setMethod("celdaModel", |
|
364 |
+ signature(sce = "SingleCellExperiment"), |
|
365 |
+ function(sce, altExpName = "featureSubset") { |
|
366 |
+ |
|
367 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
368 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
369 |
+ "selectFeatures(x) first!") |
|
370 |
+ } |
|
371 |
+ |
|
372 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
373 |
+ |
|
374 |
+ tryCatch( |
|
375 |
+ if (S4Vectors::metadata(altExp)$celda_parameters$model %in% |
|
376 |
+ c("celda_C", "celda_G", "celda_CG")) { |
|
377 |
+ return(S4Vectors::metadata(altExp)$celda_parameters$model) |
|
378 |
+ } else { |
|
379 |
+ stop("S4Vectors::metadata(altExp(sce,", |
|
380 |
+ " altExpName))$celda_parameters$model must be", |
|
381 |
+ " one of 'celda_C', 'celda_G', or 'celda_CG'") |
|
382 |
+ }, |
|
383 |
+ error = function(e) { |
|
384 |
+ message("S4Vectors::metadata(altExp(sce,", |
|
385 |
+ " altExpName))$celda_parameters$model must", |
|
386 |
+ " exist! Try running celda model (celda_C, celda_CG, or", |
|
387 |
+ " celda_G) first.") |
|
388 |
+ stop(e) |
|
389 |
+ }) |
|
390 |
+ }) |
|
391 |
+ |
|
392 |
+ |
|
393 |
+#' @title Get perplexity for every model in a celdaList |
|
394 |
+#' @description Returns perplexity for each model in a celdaList as calculated |
|
395 |
+#' by `perplexity().` |
|
396 |
+#' @param celdaList An object of class celdaList. |
|
397 |
+#' @return List. Contains one celdaModel object for each of the parameters |
|
398 |
+#' specified in the `runParams()` of the provided celda list. |
|
399 |
+#' @examples |
|
400 |
+#' data(celdaCGGridSearchRes) |
|
401 |
+#' celdaCGGridModelPerplexities <- celdaPerplexity(celdaCGGridSearchRes) |
|
402 |
+#' @export |
|
403 |
+setGeneric( |
|
404 |
+ "celdaPerplexity", |
|
405 |
+ function(celdaList) { |
|
406 |
+ standardGeneric("celdaPerplexity") |
|
407 |
+ } |
|
408 |
+) |
|
409 |
+#' @title Get perplexity for every model in a celdaList |
|
410 |
+#' @description Returns perplexity for each model in a celdaList as calculated |
|
411 |
+#' by `perplexity().` |
|
412 |
+#' @param celdaList An object of class celdaList. |
|
413 |
+#' @return List. Contains one celdaModel object for each of the parameters |
|
414 |
+#' specified in the `runParams()` of the provided celda list. |
|
415 |
+#' @examples |
|
416 |
+#' data(celdaCGGridSearchRes) |
|
417 |
+#' celdaCGGridModelPerplexities <- celdaPerplexity(celdaCGGridSearchRes) |
|
418 |
+#' @export |
|
419 |
+setMethod("celdaPerplexity", |
|
420 |
+ signature = c(celdaList = "celdaList"), |
|
421 |
+ function(celdaList) { |
|
422 |
+ celdaList@perplexity |
|
423 |
+ } |
|
424 |
+) |
|
425 |
+ |
|
426 |
+ |
|
427 |
+#' @title Get the MD5 hash of the count matrix from the celdaList |
|
428 |
+#' @description Returns the MD5 hash of the count matrix used to generate the |
|
429 |
+#' celdaList. |
|
430 |
+#' @param celdaList An object of class celdaList. |
|
431 |
+#' @return A character string of length 32 containing the MD5 digest of |
|
432 |
+#' the count matrix. |
|
433 |
+#' @examples |
|
434 |
+#' data(celdaCGGridSearchRes) |
|
435 |
+#' countChecksum <- countChecksum(celdaCGGridSearchRes) |
|
436 |
+#' @export |
|
437 |
+setGeneric( |
|
438 |
+ "countChecksum", |
|
439 |
+ function(celdaList) { |
|
440 |
+ standardGeneric("countChecksum") |
|
441 |
+ } |
|
442 |
+) |
|
443 |
+#' @title Get the MD5 hash of the count matrix from the celdaList |
|
444 |
+#' @description Returns the MD5 hash of the count matrix used to generate the |
|
445 |
+#' celdaList. |
|
446 |
+#' @param celdaList An object of class celdaList. |
|
447 |
+#' @return A character string of length 32 containing the MD5 digest of |
|
448 |
+#' the count matrix. |
|
449 |
+#' @examples |
|
450 |
+#' data(celdaCGGridSearchRes) |
|
451 |
+#' countChecksum <- countChecksum(celdaCGGridSearchRes) |
|
452 |
+#' @export |
|
453 |
+setMethod("countChecksum", |
|
454 |
+ signature = c(celdaList = "celdaList"), |
|
455 |
+ function(celdaList) { |
|
456 |
+ celdaList@countChecksum |
|
457 |
+ } |
|
458 |
+) |
... | ... |
@@ -6,14 +6,15 @@ |
6 | 6 |
#' Fixed parameters to be used in all models, such as \code{sampleLabel}, can |
7 | 7 |
#' be passed as a list to the argument \code{paramsFixed}. When |
8 | 8 |
#' \code{verbose = TRUE}, output from each chain will be sent to a log file |
9 |
-#' but not be displayed in stdout. |
|
9 |
+#' but not be displayed in \code{stdout}. |
|
10 | 10 |
#' @param x A numeric \link{matrix} of counts or a |
11 | 11 |
#' \linkS4class{SingleCellExperiment} |
12 | 12 |
#' with the matrix located in the assay slot under \code{useAssay}. |
13 | 13 |
#' Rows represent features and columns represent cells. |
14 |
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
|
15 |
-#' slot to use if \code{x} is a |
|
16 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts". |
|
14 |
+#' @param useAssay A string specifying the name of the |
|
15 |
+#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
16 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
17 |
+#' to use. Default "featureSubset". |
|
17 | 18 |
#' @param model Celda model. Options available in \link{availableModels}. |
18 | 19 |
#' @param paramsTest List. A list denoting the combinations of parameters to |
19 | 20 |
#' run in a celda model. For example, |
... | ... |
@@ -76,6 +77,7 @@ setMethod("celdaGridSearch", |
76 | 77 |
signature(x = "SingleCellExperiment"), |
77 | 78 |
function(x, |
78 | 79 |
useAssay = "counts", |
80 |
+ altExpName = "featureSubset", |
|
79 | 81 |
model, |
80 | 82 |
paramsTest, |
81 | 83 |
paramsFixed = NULL, |
... | ... |
@@ -89,7 +91,19 @@ setMethod("celdaGridSearch", |
89 | 91 |
logfilePrefix = "Celda") { |
90 | 92 |
|
91 | 93 |
xClass <- "SingleCellExperiment" |
92 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
94 |
+ |
|
95 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
96 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
97 |
+ "selectFeatures(x) first!") |
|
98 |
+ } |
|
99 |
+ |
|
100 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
101 |
+ |
|
102 |
+ if (!useAssay %in% SummarizedExperiment::assayNames(altExp)) { |
|
103 |
+ stop(useAssay, " not in assayNames(altExp(x, altExpName))") |
|
104 |
+ } |
|
105 |
+ |
|
106 |
+ counts <- SummarizedExperiment::assay(altExp, i = useAssay) |
|
93 | 107 |
|
94 | 108 |
celdaList <- .celdaGridSearch(counts = counts, |
95 | 109 |
model = paste0(".", model), |
... | ... |
@@ -104,8 +118,8 @@ setMethod("celdaGridSearch", |
104 | 118 |
verbose = verbose, |
105 | 119 |
logfilePrefix = logfilePrefix) |
106 | 120 |
|
107 |
- sce <- .createSCEceldaGridSearch(celdaList = celdaList, |
|
108 |
- sce = x, |
|
121 |
+ altExp <- .createSCEceldaGridSearch(celdaList = celdaList, |
|
122 |
+ sce = altExp, |
|
109 | 123 |
xClass = xClass, |
110 | 124 |
useAssay = useAssay, |
111 | 125 |
model = model, |
... | ... |
@@ -119,6 +133,7 @@ setMethod("celdaGridSearch", |
119 | 133 |
perplexity = perplexity, |
120 | 134 |
verbose = verbose, |
121 | 135 |
logfilePrefix = logfilePrefix) |
136 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
122 | 137 |
return(sce) |
123 | 138 |
}) |
124 | 139 |
|
... | ... |
@@ -128,6 +143,8 @@ setMethod("celdaGridSearch", |
128 | 143 |
setMethod("celdaGridSearch", |
129 | 144 |
signature(x = "matrix"), |
130 | 145 |
function(x, |
146 |
+ useAssay = "counts", |
|
147 |
+ altExpName = "featureSubset", |
|
131 | 148 |
model, |
132 | 149 |
paramsTest, |
133 | 150 |
paramsFixed = NULL, |
... | ... |
@@ -140,10 +157,12 @@ setMethod("celdaGridSearch", |
140 | 157 |
verbose = TRUE, |
141 | 158 |
logfilePrefix = "Celda") { |
142 | 159 |
|
160 |
+ ls <- list() |
|
161 |
+ ls[[useAssay]] <- x |
|
162 |
+ sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
|
163 |
+ SingleCellExperiment::altExp(sce, altExpName) <- sce |
|
143 | 164 |
xClass <- "matrix" |
144 |
- useAssay <- NULL |
|
145 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
146 |
- assays = list(counts = x)) |
|
165 |
+ |
|
147 | 166 |
celdaList <- .celdaGridSearch(counts = x, |
148 | 167 |
model = paste0(".", model), |
149 | 168 |
paramsTest = paramsTest, |
... | ... |
@@ -157,8 +176,8 @@ setMethod("celdaGridSearch", |
157 | 176 |
verbose = verbose, |
158 | 177 |
logfilePrefix = logfilePrefix) |
159 | 178 |
|
160 |
- sce <- .createSCEceldaGridSearch(celdaList = celdaList, |
|
161 |
- sce = sce, |
|
179 |
+ altExp <- .createSCEceldaGridSearch(celdaList = celdaList, |
|
180 |
+ sce = SingleCellExperiment::altExp(sce, altExpName), |
|
162 | 181 |
xClass = xClass, |
163 | 182 |
useAssay = useAssay, |
164 | 183 |
model = model, |
... | ... |
@@ -172,6 +191,7 @@ setMethod("celdaGridSearch", |
172 | 191 |
perplexity = perplexity, |
173 | 192 |
verbose = verbose, |
174 | 193 |
logfilePrefix = logfilePrefix) |
194 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
175 | 195 |
return(sce) |
176 | 196 |
}) |
177 | 197 |
|
... | ... |
@@ -422,6 +442,8 @@ setMethod("celdaGridSearch", |
422 | 442 |
#' @param useAssay A string specifying which \code{assay} |
423 | 443 |
#' slot to use if \code{x} is a |
424 | 444 |
#' \linkS4class{SingleCellExperiment} object. Default "counts". |
445 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
446 |
+#' to use. Default "featureSubset". |
|
425 | 447 |
#' @return One of |
426 | 448 |
#' \itemize{ |
427 | 449 |
#' \item A new \linkS4class{SingleCellExperiment} object containing |
... | ... |
@@ -455,13 +477,13 @@ setGeneric("subsetCeldaList", function(x, ...) { |
455 | 477 |
#' @export |
456 | 478 |
setMethod("subsetCeldaList", |
457 | 479 |
signature(x = "SingleCellExperiment"), |
458 |
- function(x, params, useAssay = "counts") { |
|
480 |
+ function(x, params, useAssay = "counts", altExpName = "featureSubset") { |
|
459 | 481 |
|
460 | 482 |
## Check for bad parameter names |
461 | 483 |
if (!all(names(params) %in% colnames(runParams(x)))) { |
462 | 484 |
badParams <- setdiff(names(params), colnames(runParams(x))) |
463 | 485 |
stop("The following elements in 'params' are not columns in", |
464 |
- " runParams (x) ", |
|
486 |
+ " runParams(x) ", |
|
465 | 487 |
paste(badParams, collapse = ",") |
466 | 488 |
) |
467 | 489 |
} |
... | ... |
@@ -481,13 +503,17 @@ setMethod("subsetCeldaList", |
481 | 503 |
|
482 | 504 |
## Get index of selected models, subset celdaList, and return |
483 | 505 |
ix <- match(newRunParams$index, runParams(x)$index) |
506 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
507 |
+ |
|
484 | 508 |
if (length(ix) == 1) { |
485 |
- x <- .subsetCeldaListSCE(x, ix) |
|
509 |
+ altExp <- .subsetCeldaListSCE(altExp, ix) |
|
486 | 510 |
} else { |
487 |
- x@metadata$celda_grid_search@runParams <- |
|
511 |
+ altExp@metadata$celda_grid_search@runParams <- |
|
488 | 512 |
as.data.frame(newRunParams) |
489 |
- x@metadata$celda_grid_search@resList <- resList(x)[ix] |
|
513 |
+ altExp@metadata$celda_grid_search@resList <- |
|
514 |
+ altExp@metadata$celda_grid_search@resList[ix] |
|
490 | 515 |
} |
516 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
491 | 517 |
return(x) |
492 | 518 |
} |
493 | 519 |
) |
... | ... |
@@ -555,6 +581,8 @@ setMethod("subsetCeldaList", |
555 | 581 |
#' @param useAssay A string specifying which \code{assay} |
556 | 582 |
#' slot to use if \code{x} is a |
557 | 583 |
#' \linkS4class{SingleCellExperiment} object. Default "counts". |
584 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
585 |
+#' to use. Default "featureSubset". |
|
558 | 586 |
#' @return One of |
559 | 587 |
#' \itemize{ |
560 | 588 |
#' \item A new \linkS4class{SingleCellExperiment} object containing |
... | ... |
@@ -585,11 +613,14 @@ setGeneric("selectBestModel", function(x, ...) { |
585 | 613 |
#' @importFrom data.table as.data.table |
586 | 614 |
#' @export |
587 | 615 |
setMethod("selectBestModel", signature(x = "SingleCellExperiment"), |
588 |
- function(x, asList = FALSE, useAssay = "counts") { |
|
616 |
+ function(x, asList = FALSE, useAssay = "counts", |
|
617 |
+ altExpName = "featureSubset") { |
|
618 |
+ |
|
619 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
589 | 620 |
logLikelihood <- NULL |
590 | 621 |
group <- setdiff(colnames(runParams(x)), |
591 | 622 |
c("index", "chain", "logLikelihood", "mean_perplexity", "seed")) |
592 |
- runParams <- S4Vectors::metadata(x)$celda_grid_search@runParams |
|
623 |
+ runParams <- S4Vectors::metadata(altExp)$celda_grid_search@runParams |
|
593 | 624 |
dt <- data.table::as.data.table(runParams) |
594 | 625 |
newRunParams <- as.data.frame(dt[, .SD[which.max(logLikelihood)], |
595 | 626 |
by = group]) |
... | ... |
@@ -597,12 +628,14 @@ setMethod("selectBestModel", signature(x = "SingleCellExperiment"), |
597 | 628 |
|
598 | 629 |
ix <- match(newRunParams$index, runParams$index) |
599 | 630 |
if (nrow(newRunParams) == 1 & !asList) { |
600 |
- x <- .subsetCeldaListSCE(x, ix) |
|
631 |
+ altExp <- .subsetCeldaListSCE(altExp, ix) |
|
601 | 632 |
} else { |
602 |
- x@metadata$celda_grid_search@runParams <- |
|
633 |
+ altExp@metadata$celda_grid_search@runParams <- |
|
603 | 634 |
as.data.frame(newRunParams) |
604 |
- x@metadata$celda_grid_search@resList <- resList(x)[ix] |
|
635 |
+ altExp@metadata$celda_grid_search@resList <- |
|
636 |
+ altExp@metadata$celda_grid_search@resList[ix] |
|
605 | 637 |
} |
638 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
606 | 639 |
return(x) |
607 | 640 |
} |
608 | 641 |
) |
... | ... |
@@ -676,7 +709,8 @@ setMethod("selectBestModel", signature(x = "celdaList"), |
676 | 709 |
.subsetCeldaListSCE <- function(x, ix) { |
677 | 710 |
cgsparam <- x@metadata$celda_grid_search@celdaGridSearchParameters |
678 | 711 |
if (cgsparam$model == "celda_C") { |
679 |
- x <- .createSCEceldaC(celdaCMod = resList(x)[[ix]], |
|
712 |
+ x <- .createSCEceldaC(celdaCMod = |
|
713 |
+ x@metadata$celda_grid_search@resList[[ix]], |
|
680 | 714 |
sce = x, |
681 | 715 |
xClass = cgsparam$xClass, |
682 | 716 |
useAssay = cgsparam$useAssay, |
... | ... |
@@ -691,7 +725,8 @@ setMethod("selectBestModel", signature(x = "celdaList"), |
691 | 725 |
logfile = cgsparam$logfile, |
692 | 726 |
verbose = cgsparam$verbose) |
693 | 727 |
} else if (cgsparam$model == "celda_G") { |
694 |
- x <- .createSCEceldaG(celdaGMod = resList(x)[[ix]], |
|
728 |
+ x <- .createSCEceldaG(celdaGMod = |
|
729 |
+ x@metadata$celda_grid_search@resList[[ix]], |
|
695 | 730 |
sce = x, |
696 | 731 |
xClass = cgsparam$xClass, |
697 | 732 |
useAssay = cgsparam$useAssay, |
... | ... |
@@ -705,7 +740,8 @@ setMethod("selectBestModel", signature(x = "celdaList"), |
705 | 740 |
logfile = cgsparam$logfile, |
706 | 741 |
verbose = cgsparam$verbose) |
707 | 742 |
} else if (cgsparam$model == "celda_CG") { |
708 |
- x <- .createSCEceldaCG(celdaCGMod = resList(x)[[ix]], |
|
743 |
+ x <- .createSCEceldaCG(celdaCGMod = |
|
744 |
+ x@metadata$celda_grid_search@resList[[ix]], |
|
709 | 745 |
sce = x, |
710 | 746 |
xClass = cgsparam$xClass, |
711 | 747 |
useAssay = cgsparam$useAssay, |
... | ... |
@@ -722,7 +758,7 @@ setMethod("selectBestModel", signature(x = "celdaList"), |
722 | 758 |
logfile = cgsparam$logfile, |
723 | 759 |
verbose = cgsparam$verbose) |
724 | 760 |
} else { |
725 |
- stop("S4Vectors::metadata(X)$celda_grid_search@", |
|
761 |
+ stop("S4Vectors::metadata(altExp(x, altExpName))$celda_grid_search@", |
|
726 | 762 |
"celdaGridSearchParameters$model must be", |
727 | 763 |
" one of 'celda_C', 'celda_G', or 'celda_CG'") |
728 | 764 |
} |
... | ... |
@@ -6,6 +6,8 @@ |
6 | 6 |
#' returned by \link{celda_C}, \link{celda_G}, or \link{celda_CG}. |
7 | 7 |
#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
8 | 8 |
#' slot to use. Default "counts". |
9 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
10 |
+#' to use. Default "featureSubset". |
|
9 | 11 |
#' @param level Character. One of "cellPopulation" or "Sample". |
10 | 12 |
#' "cellPopulation" will display the absolute probabilities and relative |
11 | 13 |
#' normalized expression of each module in each cell population. |
... | ... |
@@ -33,19 +35,23 @@ setGeneric("celdaProbabilityMap", |
33 | 35 |
#' celdaProbabilityMap(sceCeldaCG) |
34 | 36 |
#' @export |
35 | 37 |
setMethod("celdaProbabilityMap", signature(sce = "SingleCellExperiment"), |
36 |
- function(sce, useAssay = "counts", level = c("cellPopulation", "sample")) { |
|
38 |
+ function(sce, useAssay = "counts", altExpName = "featureSubset", |
|
39 |
+ level = c("cellPopulation", "sample")) { |
|
40 |
+ |
|
41 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
37 | 42 |
level <- match.arg(level) |
38 | 43 |
if (celdaModel(sce) == "celda_C") { |
39 | 44 |
if (level == "cellPopulation") { |
40 | 45 |
warning("'level' has been set to 'sample'") |
41 | 46 |
} |
42 |
- pm <- .celdaProbabilityMapC(sce = sce, useAssay = useAssay, |
|
47 |
+ pm <- .celdaProbabilityMapC(sce = altExp, useAssay = useAssay, |
|
43 | 48 |
level = "sample") |
44 | 49 |
} else if (celdaModel(sce) == "celda_CG") { |
45 |
- pm <- .celdaProbabilityMapCG(sce = sce, useAssay = useAssay, |
|
50 |
+ pm <- .celdaProbabilityMapCG(sce = altExp, useAssay = useAssay, |
|
46 | 51 |
level = level) |
47 | 52 |
} else { |
48 |
- stop("S4Vectors::metadata(sce)$celda_parameters$model must be", |
|
53 |
+ stop("S4Vectors::metadata(altExp(sce,", |
|
54 |
+ " altExpName))$celda_parameters$model must be", |
|
49 | 55 |
" one of 'celda_C', or 'celda_CG'!") |
50 | 56 |
} |
51 | 57 |
return(pm) |
... | ... |
@@ -57,10 +63,12 @@ setMethod("celdaProbabilityMap", signature(sce = "SingleCellExperiment"), |
57 | 63 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
58 | 64 |
counts <- .processCounts(counts) |
59 | 65 |
|
60 |
- zInclude <- which(tabulate(celdaClusters(sce), |
|
66 |
+ zInclude <- which(tabulate(SummarizedExperiment::colData( |
|
67 |
+ sce)$celda_cell_cluster, |
|
61 | 68 |
S4Vectors::metadata(sce)$celda_parameters$K) > 0) |
62 | 69 |
|
63 |
- factorized <- factorizeMatrix(x = sce, useAssay = useAssay) |
|
70 |
+ factorized <- .factorizeMatrixCelda_C(x = sce, useAssay = useAssay, |
|
71 |
+ type = "proportion") |
|
64 | 72 |
|
65 | 73 |
samp <- factorized$proportions$sample[zInclude, , drop = FALSE] |
66 | 74 |
col <- grDevices::colorRampPalette(c("white", |
... | ... |
@@ -108,22 +116,23 @@ setMethod("celdaProbabilityMap", signature(sce = "SingleCellExperiment"), |
108 | 116 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
109 | 117 |
counts <- .processCounts(counts) |
110 | 118 |
|
111 |
- factorized <- factorizeMatrix(sce, useAssay) |
|
112 |
- zInclude <- which(tabulate(celdaClusters(sce), |
|
119 |
+ factorized <- .factorizeMatrixCelda_CG(sce, useAssay, |
|
120 |
+ type = c("counts", "proportion")) |
|
121 |
+ zInclude <- which(tabulate(SummarizedExperiment::colData( |
|
122 |
+ sce)$celda_cell_cluster, |
|
113 | 123 |
S4Vectors::metadata(sce)$celda_parameters$K) > 0) |
114 |
- yInclude <- which(tabulate(celdaModules(sce), |
|
124 |
+ yInclude <- which(tabulate(SummarizedExperiment::rowData( |
|
125 |
+ sce)$celda_feature_module, |
|
115 | 126 |
S4Vectors::metadata(sce)$celda_parameters$L) > 0) |
116 | 127 |
|
117 | 128 |
if (level == "cellPopulation") { |
118 | 129 |
pop <- factorized$proportions$cellPopulation[yInclude, |
119 | 130 |
zInclude, |
120 |
- drop = FALSE |
|
121 |
- ] |
|
131 |
+ drop = FALSE] |
|
122 | 132 |
popNorm <- normalizeCounts(pop, |
123 | 133 |
normalize = "proportion", |
124 | 134 |
transformationFun = sqrt, |
125 |
- scaleFun = base::scale |
|
126 |
- ) |
|
135 |
+ scaleFun = base::scale) |
|
127 | 136 |
|
128 | 137 |
percentile9 <- round(stats::quantile(pop, .9), digits = 2) * 100 |
129 | 138 |
col1 <- grDevices::colorRampPalette(c( |
... | ... |
@@ -10,6 +10,8 @@ |
10 | 10 |
#' returned by \link{celda_C}, \link{celda_G}, or \link{celda_CG}. |
11 | 11 |
#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
12 | 12 |
#' slot to use. Default "counts". |
13 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
14 |
+#' to use. Default "featureSubset". |
|
13 | 15 |
#' @param maxCells Integer. Maximum number of cells to plot. Cells will be |
14 | 16 |
#' randomly subsampled if \code{ncol(sce) > maxCells}. Larger numbers of cells |
15 | 17 |
#' requires more memory. If NULL, no subsampling will be performed. |
... | ... |
@@ -76,6 +78,7 @@ setGeneric("celdaUmap", |
76 | 78 |
setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
77 | 79 |
function(sce, |
78 | 80 |
useAssay = "counts", |
81 |
+ altExpName = "featureSubset", |
|
79 | 82 |
maxCells = NULL, |
80 | 83 |
minClusterSize = 100, |
81 | 84 |
modules = NULL, |
... | ... |
@@ -92,8 +95,9 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
92 | 95 |
...) { |
93 | 96 |
|
94 | 97 |
if (is.null(seed)) { |
95 |
- res <- .celdaUmap(sce = sce, |
|
98 |
+ sce <- .celdaUmap(sce = sce, |
|
96 | 99 |
useAssay = useAssay, |
100 |
+ altExpName = altExpName, |
|
97 | 101 |
maxCells = maxCells, |
98 | 102 |
minClusterSize = minClusterSize, |
99 | 103 |
modules = modules, |
... | ... |
@@ -110,8 +114,9 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
110 | 114 |
...) |
111 | 115 |
} else { |
112 | 116 |
with_seed(seed, |
113 |
- res <- .celdaUmap(sce = sce, |
|
117 |
+ sce <- .celdaUmap(sce = sce, |
|
114 | 118 |
useAssay = useAssay, |
119 |
+ altExpName = altExpName, |
|
115 | 120 |
maxCells = maxCells, |
116 | 121 |
minClusterSize = minClusterSize, |
117 | 122 |
modules = modules, |
... | ... |
@@ -127,8 +132,6 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
127 | 132 |
cores = cores, |
128 | 133 |
...)) |
129 | 134 |
} |
130 |
- |
|
131 |
- SingleCellExperiment::reducedDim(sce, "celda_UMAP") <- res |
|
132 | 135 |
return(sce) |
133 | 136 |
}) |
134 | 137 |
|
... | ... |
@@ -151,9 +154,10 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
151 | 154 |
...) { |
152 | 155 |
|
153 | 156 |
celdaMod <- celdaModel(sce) |
157 |
+ altExp <- SingleCellExperiment::altExp(sce, altExpName) |
|
154 | 158 |
|
155 | 159 |
if (celdaMod == "celda_C") { |
156 |
- res <- .celdaUmapC(sce = sce, |
|
160 |
+ res <- .celdaUmapC(sce = altExp, |
|
157 | 161 |
useAssay = useAssay, |
158 | 162 |
maxCells = maxCells, |
159 | 163 |
minClusterSize = minClusterSize, |
... | ... |
@@ -168,7 +172,7 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
168 | 172 |
cores = cores, |
169 | 173 |
...) |
170 | 174 |
} else if (celdaMod == "celda_CG") { |
171 |
- res <- .celdaUmapCG(sce = sce, |
|
175 |
+ res <- .celdaUmapCG(sce = altExp, |
|
172 | 176 |
useAssay = useAssay, |
173 | 177 |
maxCells = maxCells, |
174 | 178 |
minClusterSize = minClusterSize, |
... | ... |
@@ -183,7 +187,7 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
183 | 187 |
cores = cores, |
184 | 188 |
...) |
185 | 189 |
} else if (celdaMod == "celda_G") { |
186 |
- res <- .celdaUmapG(sce = sce, |
|
190 |
+ res <- .celdaUmapG(sce = altExp, |
|
187 | 191 |
useAssay = useAssay, |
188 | 192 |
maxCells = maxCells, |
189 | 193 |
minClusterSize = minClusterSize, |
... | ... |
@@ -198,10 +202,12 @@ setMethod("celdaUmap", signature(sce = "SingleCellExperiment"), |
198 | 202 |
cores = cores, |
199 | 203 |
...) |
200 | 204 |
} else { |
201 |
- stop("S4Vectors::metadata(sce)$celda_parameters$model must be", |
|
205 |
+ stop("S4Vectors::metadata(altExp(sce, altExpName))$", |
|
206 |
+ "celda_parameters$model must be", |
|
202 | 207 |
" one of 'celda_C', 'celda_G', or 'celda_CG'") |
203 | 208 |
} |
204 |
- return(res) |
|
209 |
+ SingleCellExperiment::reducedDim(sce, "celda_UMAP") <- res |
|
210 |
+ return(sce) |
|
205 | 211 |
|
206 | 212 |
} |
207 | 213 |
|
... | ... |
@@ -1,13 +1,20 @@ |
1 | 1 |
#' @title Cell clustering with Celda |
2 | 2 |
#' @description Clusters the columns of a count matrix containing single-cell |
3 |
-#' data into K subpopulations. |
|
3 |
+#' data into K subpopulations. The |
|
4 |
+#' \code{useAssay} \link[SummarizedExperiment]{assay} slot in |
|
5 |
+#' \code{altExpName} \link[SingleCellExperiment]{altExp} slot will be used if |
|
6 |
+#' it exists. Otherwise, the \code{useAssay} |
|
7 |
+#' \link[SummarizedExperiment]{assay} slot in \code{x} will be used if |
|
8 |
+#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
|
4 | 9 |
#' @param x A numeric \link{matrix} of counts or a |
5 | 10 |
#' \linkS4class{SingleCellExperiment} |
6 |
-#' with the matrix located in the assay slot under \code{useAssay}. |
|
11 |
+#' with the matrix located in the assay slot under \code{useAssay} in |
|
12 |
+#' \code{altExp(x, altExpName)}. |
|
7 | 13 |
#' Rows represent features and columns represent cells. |
8 |
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
|
9 |
-#' slot to use if \code{x} is a |
|
10 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts". |
|
14 |
+#' @param useAssay A string specifying the name of the |
|
15 |
+#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
16 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
17 |
+#' to use. Default "featureSubset". |
|
11 | 18 |
#' @param sampleLabel Vector or factor. Denotes the sample label for each cell |
12 | 19 |
#' (column) in the count matrix. |
13 | 20 |
#' @param K Integer. Number of cell populations. |
... | ... |
@@ -79,6 +86,7 @@ setMethod("celda_C", |
79 | 86 |
signature(x = "SingleCellExperiment"), |
80 | 87 |
function(x, |
81 | 88 |
useAssay = "counts", |
89 |
+ altExpName = "featureSubset", |
|
82 | 90 |
sampleLabel = NULL, |
83 | 91 |
K, |
84 | 92 |
alpha = 1, |
... | ... |
@@ -97,12 +105,24 @@ setMethod("celda_C", |
97 | 105 |
verbose = TRUE) { |
98 | 106 |
|
99 | 107 |
xClass <- "SingleCellExperiment" |
100 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
101 | 108 |
|
102 |
- sce <- .celdaCWithSeed(counts = counts, |
|
109 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
110 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
111 |
+ "selectFeatures(x) first!") |
|
112 |
+ } |
|
113 |
+ |
|
114 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
115 |
+ |
|
116 |
+ if (!useAssay %in% SummarizedExperiment::assayNames(altExp)) { |
|
117 |
+ stop(useAssay, " not in assayNames(altExp(x, altExpName))") |
|
118 |
+ } |
|
119 |
+ |
|
120 |
+ counts <- SummarizedExperiment::assay(altExp, i = useAssay) |
|
121 |
+ |
|
122 |
+ altExp <- .celdaCWithSeed(counts = counts, |
|
103 | 123 |
xClass = xClass, |
104 | 124 |
useAssay = useAssay, |
105 |
- sce = x, |
|
125 |
+ sce = altExp, |
|
106 | 126 |
sampleLabel = sampleLabel, |
107 | 127 |
K = K, |
108 | 128 |
alpha = alpha, |
... | ... |
@@ -119,7 +139,8 @@ setMethod("celda_C", |
119 | 139 |
zInit = zInit, |
120 | 140 |
logfile = logfile, |
121 | 141 |
verbose = verbose) |
122 |
- return(sce) |
|
142 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
143 |
+ return(x) |
|
123 | 144 |
} |
124 | 145 |
) |
125 | 146 |
|
... | ... |
@@ -129,6 +150,8 @@ setMethod("celda_C", |
129 | 150 |
setMethod("celda_C", |
130 | 151 |
signature(x = "matrix"), |
131 | 152 |
function(x, |
153 |
+ useAssay = "counts", |
|
154 |
+ altExpName = "featureSubset", |
|
132 | 155 |
sampleLabel = NULL, |
133 | 156 |
K, |
134 | 157 |
alpha = 1, |
... | ... |
@@ -146,14 +169,16 @@ setMethod("celda_C", |
146 | 169 |
logfile = NULL, |
147 | 170 |
verbose = TRUE) { |
148 | 171 |
|
172 |
+ ls <- list() |
|
173 |
+ ls[[useAssay]] <- x |
|
174 |
+ sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
|
175 |
+ SingleCellExperiment::altExp(sce, altExpName) <- sce |
|
149 | 176 |
xClass <- "matrix" |
150 |
- useAssay <- NULL |
|
151 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
152 |
- assays = list(counts = x)) |
|
177 |
+ |
|
153 | 178 |
sce <- .celdaCWithSeed(counts = x, |
154 | 179 |
xClass = xClass, |
155 | 180 |
useAssay = useAssay, |
156 |
- sce = sce, |
|
181 |
+ sce = SingleCellExperiment::altExp(sce, altExpName), |
|
157 | 182 |
sampleLabel = sampleLabel, |
158 | 183 |
K = K, |
159 | 184 |
alpha = alpha, |
... | ... |
@@ -170,6 +195,7 @@ setMethod("celda_C", |
170 | 195 |
zInit = zInit, |
171 | 196 |
logfile = logfile, |
172 | 197 |
verbose = verbose) |
198 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
173 | 199 |
return(sce) |
174 | 200 |
} |
175 | 201 |
) |
... | ... |
@@ -841,7 +867,7 @@ setMethod("celda_C", |
841 | 867 |
zInclude <- rep(TRUE, ncol(counts)) |
842 | 868 |
|
843 | 869 |
if (totalCellsToRemove > 0) { |
844 |
- zTa <- tabulate(celdaClusters(sce), |
|
870 |
+ zTa <- tabulate(SummarizedExperiment::colData(sce)$celda_cell_cluster, |
|
845 | 871 |
S4Vectors::metadata(sce)$celda_parameters$K) |
846 | 872 |
|
847 | 873 |
## Number of cells that can be sampled from each cluster without |
... | ... |
@@ -860,7 +886,8 @@ setMethod("celda_C", |
860 | 886 |
|
861 | 887 |
## Perform sampling for each cluster |
862 | 888 |
for (i in which(clusterNToSample > 0)) { |
863 |
- zInclude[sample(which(celdaClusters(sce) == i), |
|
889 |
+ zInclude[sample(which( |
|
890 |
+ SummarizedExperiment::colData(sce)$celda_cell_cluster == i), |
|
864 | 891 |
clusterNToSample[i])] <- FALSE |
865 | 892 |
} |
866 | 893 |
} |
... | ... |
@@ -1,13 +1,20 @@ |
1 | 1 |
#' @title Cell and feature clustering with Celda |
2 | 2 |
#' @description Clusters the rows and columns of a count matrix containing |
3 |
-#' single-cell data into L modules and K subpopulations, respectively. |
|
3 |
+#' single-cell data into L modules and K subpopulations, respectively. The |
|
4 |
+#' \code{useAssay} \link[SummarizedExperiment]{assay} slot in |
|
5 |
+#' \code{altExpName} \link[SingleCellExperiment]{altExp} slot will be used if |
|
6 |
+#' it exists. Otherwise, the \code{useAssay} |
|
7 |
+#' \link[SummarizedExperiment]{assay} slot in \code{x} will be used if |
|
8 |
+#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
|
4 | 9 |
#' @param x A numeric \link{matrix} of counts or a |
5 | 10 |
#' \linkS4class{SingleCellExperiment} |
6 |
-#' with the matrix located in the assay slot under \code{useAssay}. |
|
11 |
+#' with the matrix located in the \link[SummarizedExperiment]{assay} |
|
12 |
+#' slot under \code{useAssay} in \code{altExp(x, altExpName)}. |
|
7 | 13 |
#' Rows represent features and columns represent cells. |
8 |
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
|
9 |
-#' slot to use if \code{x} is a |
|
10 |
-#' \linkS4class{SingleCellExperiment} object. Default "counts". |
|
14 |
+#' @param useAssay A string specifying the name of the |
|
15 |
+#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
16 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
17 |
+#' to use. Default "featureSubset". |
|
11 | 18 |
#' @param sampleLabel Vector or factor. Denotes the sample label for each cell |
12 | 19 |
#' (column) in the count matrix. |
13 | 20 |
#' @param K Integer. Number of cell populations. |
... | ... |
@@ -62,23 +69,17 @@ |
62 | 69 |
#' @param logfile Character. Messages will be redirected to a file named |
63 | 70 |
#' `logfile`. If NULL, messages will be printed to stdout. Default NULL. |
64 | 71 |
#' @param verbose Logical. Whether to print log messages. Default TRUE. |
65 |
-#' @return A \link[SingleCellExperiment]{SingleCellExperiment} object. Function |
|
66 |
-#' parameter settings are stored in the \link[S4Vectors]{metadata} |
|
67 |
-#' \code{"celda_parameters"} slot. |
|
68 |
-#' Columns \code{celda_sample_label} and \code{celda_cell_cluster} in |
|
72 |
+#' @return A \linkS4class{SingleCellExperiment} object. Function |
|
73 |
+#' parameter settings are stored in \link[S4Vectors]{metadata} |
|
74 |
+#' \code{"celda_parameters"} in \link[SingleCellExperiment]{altExp} slot. |
|
75 |
+#' In \link[SingleCellExperiment]{altExp} slot, |
|
76 |
+#' columns \code{celda_sample_label} and \code{celda_cell_cluster} in |
|
69 | 77 |
#' \link[SummarizedExperiment]{colData} contain sample labels and celda cell |
70 | 78 |
#' population clusters. Column \code{celda_feature_module} in |
71 | 79 |
#' \link[SummarizedExperiment]{rowData} contains feature modules. |
72 | 80 |
#' @seealso \link{celda_G} for feature clustering and \link{celda_C} for |
73 | 81 |
#' clustering cells. \link{celdaGridSearch} can be used to run multiple |
74 | 82 |
#' values of K/L and multiple chains in parallel. |
75 |
-#' @examples |
|
76 |
-#' data(celdaCGSim) |
|
77 |
-#' sce <- celda_CG(celdaCGSim$counts, |
|
78 |
-#' K = celdaCGSim$K, |
|
79 |
-#' L = celdaCGSim$L, |
|
80 |
-#' sampleLabel = celdaCGSim$sampleLabel, |
|
81 |
-#' nchains = 1) |
|
82 | 83 |
#' @import Rcpp RcppEigen |
83 | 84 |
#' @rawNamespace import(gridExtra, except = c(combine)) |
84 | 85 |
#' @export |
... | ... |
@@ -92,6 +93,7 @@ setMethod("celda_CG", |
92 | 93 |
signature(x = "SingleCellExperiment"), |
93 | 94 |
function(x, |
94 | 95 |
useAssay = "counts", |
96 |
+ altExpName = "featureSubset", |
|
95 | 97 |
sampleLabel = NULL, |
96 | 98 |
K, |
97 | 99 |
L, |
... | ... |
@@ -115,12 +117,24 @@ setMethod("celda_CG", |
115 | 117 |
verbose = TRUE) { |
116 | 118 |
|
117 | 119 |
xClass <- "SingleCellExperiment" |
118 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
119 | 120 |
|
120 |
- sce <- .celdaCGWithSeed(counts = counts, |
|
121 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
122 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
123 |
+ "selectFeatures(x) first!") |
|
124 |
+ } |
|
125 |
+ |
|
126 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
127 |
+ |
|
128 |
+ if (!useAssay %in% SummarizedExperiment::assayNames(altExp)) { |
|
129 |
+ stop(useAssay, " not in assayNames(altExp(x, altExpName))") |
|
130 |
+ } |
|
131 |
+ |
|
132 |
+ counts <- SummarizedExperiment::assay(altExp, i = useAssay) |
|
133 |
+ |
|
134 |
+ altExp <- .celdaCGWithSeed(counts = counts, |
|
121 | 135 |
xClass = xClass, |
122 | 136 |
useAssay = useAssay, |
123 |
- sce = x, |
|
137 |
+ sce = altExp, |
|
124 | 138 |
sampleLabel = sampleLabel, |
125 | 139 |
K = K, |
126 | 140 |
L = L, |
... | ... |
@@ -142,16 +156,26 @@ setMethod("celda_CG", |
142 | 156 |
yInit = yInit, |
143 | 157 |
logfile = logfile, |
144 | 158 |
verbose = verbose) |
145 |
- return(sce) |
|
159 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
160 |
+ return(x) |
|
146 | 161 |
} |
147 | 162 |
) |
148 | 163 |
|
149 | 164 |
|
150 | 165 |
#' @rdname celda_CG |
166 |
+#' @examples |
|
167 |
+#' data(celdaCGSim) |
|
168 |
+#' sce <- celda_CG(celdaCGSim$counts, |
|
169 |
+#' K = celdaCGSim$K, |
|
170 |
+#' L = celdaCGSim$L, |
|
171 |
+#' sampleLabel = celdaCGSim$sampleLabel, |
|
172 |
+#' nchains = 1) |
|
151 | 173 |
#' @export |
152 | 174 |
setMethod("celda_CG", |
153 | 175 |
signature(x = "matrix"), |
154 | 176 |
function(x, |
177 |
+ useAssay = "counts", |
|
178 |
+ altExpName = "featureSubset", |
|
155 | 179 |
sampleLabel = NULL, |
156 | 180 |
K, |
157 | 181 |
L, |
... | ... |
@@ -174,14 +198,16 @@ setMethod("celda_CG", |
174 | 198 |
logfile = NULL, |
175 | 199 |
verbose = TRUE) { |
176 | 200 |
|
201 |
+ ls <- list() |
|
202 |
+ ls[[useAssay]] <- x |
|
203 |
+ sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
|
204 |
+ SingleCellExperiment::altExp(sce, altExpName) <- sce |
|
177 | 205 |
xClass <- "matrix" |
178 |
- useAssay <- NULL |
|
179 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
180 |
- assays = list(counts = x)) |
|
181 |
- sce <- .celdaCGWithSeed(counts = x, |
|
206 |
+ |
|
207 |
+ altExp <- .celdaCGWithSeed(counts = x, |
|
182 | 208 |
xClass = xClass, |
183 | 209 |
useAssay = useAssay, |
184 |
- sce = sce, |
|
210 |
+ sce = SingleCellExperiment::altExp(sce, altExpName), |
|
185 | 211 |
sampleLabel = sampleLabel, |
186 | 212 |
K = K, |
187 | 213 |
L = L, |
... | ... |
@@ -203,6 +229,7 @@ setMethod("celda_CG", |
203 | 229 |
yInit = yInit, |
204 | 230 |
logfile = logfile, |
205 | 231 |
verbose = verbose) |
232 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
206 | 233 |
return(sce) |
207 | 234 |
} |
208 | 235 |
) |
... | ... |
@@ -938,9 +965,7 @@ setMethod("celda_CG", |
938 | 965 |
maxCells <- ncol(counts) |
939 | 966 |
} |
940 | 967 |
|
941 |
- fm <- factorizeMatrix(sce, |
|
942 |
- useAssay, |
|
943 |
- type = "counts") |
|
968 |
+ fm <- .factorizeMatrixCelda_CG(sce, useAssay, type = "counts") |
|
944 | 969 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
945 | 970 |
if (!is.null(modules)) { |
946 | 971 |
if (!all(modules %in% modulesToUse)) { |
... | ... |
@@ -956,7 +981,7 @@ setMethod("celda_CG", |
956 | 981 |
zInclude <- rep(TRUE, ncol(counts)) |
957 | 982 |
|
958 | 983 |
if (totalCellsToRemove > 0) { |
959 |
- zTa <- tabulate(celdaClusters(sce), |
|
984 |
+ zTa <- tabulate(SummarizedExperiment::colData(sce)$celda_cell_cluster, |
|
960 | 985 |
S4Vectors::metadata(sce)$celda_parameters$K) |
961 | 986 |
|
962 | 987 |
## Number of cells that can be sampled from each cluster without |
... | ... |
@@ -976,7 +1001,8 @@ setMethod("celda_CG", |
976 | 1001 |
## Perform sampling for each cluster |
977 | 1002 |
for (i in which(clusterNToSample > 0)) { |
978 | 1003 |
zInclude[sample( |
979 |
- which(celdaClusters(sce) == i), |
|
1004 |
+ which(SummarizedExperiment::colData(sce)$celda_cell_cluster == |
|
1005 |
+ i), |
|
980 | 1006 |
clusterNToSample[i] |
981 | 1007 |
)] <- FALSE |
982 | 1008 |
} |
... | ... |
@@ -1,13 +1,19 @@ |
1 | 1 |
#' @title Feature clustering with Celda |
2 | 2 |
#' @description Clusters the rows of a count matrix containing single-cell data |
3 |
-#' into L modules. |
|
3 |
+#' into L modules. The |
|
4 |
+#' \code{useAssay} \link[SummarizedExperiment]{assay} slot in |
|
5 |
+#' \code{altExpName} \link[SingleCellExperiment]{altExp} slot will be used if |
|
6 |
+#' it exists. Otherwise, the \code{useAssay} |
|
7 |
+#' \link[SummarizedExperiment]{assay} slot in \code{x} will be used if |
|
8 |
+#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
|
4 | 9 |
#' @param x A numeric \link{matrix} of counts or a |
5 | 10 |
#' \linkS4class{SingleCellExperiment} |
6 | 11 |
#' with the matrix located in the assay slot under \code{useAssay}. |
7 | 12 |
#' Rows represent features and columns represent cells. |
8 |
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
|
9 |
-#' slot to use if \code{x} is a |
|
10 |
-#' \linkS4class{SingleCellExperiment} object. Default "counts". |
|
13 |
+#' @param useAssay A string specifying the name of the |
|
14 |
+#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
15 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
16 |
+#' to use. Default "featureSubset". |
|
11 | 17 |
#' @param L Integer. Number of feature modules. |
12 | 18 |
#' @param beta Numeric. Concentration parameter for Phi. Adds a pseudocount to |
13 | 19 |
#' each feature module in each cell. Default 1. |
... | ... |
@@ -66,6 +72,7 @@ setMethod("celda_G", |
66 | 72 |
signature(x = "SingleCellExperiment"), |
67 | 73 |
function(x, |
68 | 74 |
useAssay = "counts", |
75 |
+ altExpName = "featureSubset", |
|
69 | 76 |
L, |
70 | 77 |
beta = 1, |
71 | 78 |
delta = 1, |
... | ... |
@@ -83,12 +90,24 @@ setMethod("celda_G", |
83 | 90 |
verbose = TRUE) { |
84 | 91 |
|
85 | 92 |
xClass <- "SingleCellExperiment" |
86 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
87 | 93 |
|
88 |
- sce <- .celdaGWithSeed(counts = counts, |
|
94 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
95 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
96 |
+ "selectFeatures(x) first!") |
|
97 |
+ } |
|
98 |
+ |
|
99 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
100 |
+ |
|
101 |
+ if (!useAssay %in% SummarizedExperiment::assayNames(altExp)) { |
|
102 |
+ stop(useAssay, " not in assayNames(altExp(x, altExpName))") |
|
103 |
+ } |
|
104 |
+ |
|
105 |
+ counts <- SummarizedExperiment::assay(altExp, i = useAssay) |
|
106 |
+ |
|
107 |
+ altExp <- .celdaGWithSeed(counts = counts, |
|
89 | 108 |
xClass = xClass, |
90 | 109 |
useAssay = useAssay, |
91 |
- sce = x, |
|
110 |
+ sce = altExp, |
|
92 | 111 |
L = L, |
93 | 112 |
beta = beta, |
94 | 113 |
delta = delta, |
... | ... |
@@ -104,7 +123,8 @@ setMethod("celda_G", |
104 | 123 |
yInit = yInit, |
105 | 124 |
logfile = logfile, |
106 | 125 |
verbose = verbose) |
107 |
- return(sce) |
|
126 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
127 |
+ return(x) |
|
108 | 128 |
} |
109 | 129 |
) |
110 | 130 |
|
... | ... |
@@ -114,6 +134,8 @@ setMethod("celda_G", |
114 | 134 |
setMethod("celda_G", |
115 | 135 |
signature(x = "matrix"), |
116 | 136 |
function(x, |
137 |
+ useAssay = "counts", |
|
138 |
+ altExpName = "featureSubset", |
|
117 | 139 |
L, |
118 | 140 |
beta = 1, |
119 | 141 |
delta = 1, |
... | ... |
@@ -130,14 +152,16 @@ setMethod("celda_G", |
130 | 152 |
logfile = NULL, |
131 | 153 |
verbose = TRUE) { |
132 | 154 |
|
155 |
+ ls <- list() |
|
156 |
+ ls[[useAssay]] <- x |
|
157 |
+ sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
|
158 |
+ SingleCellExperiment::altExp(sce, altExpName) <- sce |
|
133 | 159 |
xClass <- "matrix" |
134 |
- useAssay <- NULL |
|
135 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
136 |
- assays = list(counts = x)) |
|
137 |
- sce <- .celdaGWithSeed(counts = x, |
|
160 |
+ |
|
161 |
+ altExp <- .celdaGWithSeed(counts = x, |
|
138 | 162 |
xClass = xClass, |
139 | 163 |
useAssay = useAssay, |
140 |
- sce = sce, |
|
164 |
+ sce = SingleCellExperiment::altExp(sce, altExpName), |
|
141 | 165 |
L = L, |
142 | 166 |
beta = beta, |
143 | 167 |
delta = delta, |
... | ... |
@@ -153,6 +177,7 @@ setMethod("celda_G", |
153 | 177 |
yInit = yInit, |
154 | 178 |
logfile = logfile, |
155 | 179 |
verbose = verbose) |
180 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
156 | 181 |
return(sce) |
157 | 182 |
} |
158 | 183 |
) |
... | ... |
@@ -738,7 +763,7 @@ setMethod("celda_G", |
738 | 763 |
cellIx <- sample(seq(ncol(counts)), maxCells) |
739 | 764 |
} |
740 | 765 |
|
741 |
- fm <- factorizeMatrix(x = sce, useAssay = useAssay, type = "counts") |
|
766 |
+ fm <- .factorizeMatrixCelda_G(x = sce, useAssay = useAssay, type = "counts") |
|
742 | 767 |
|
743 | 768 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
744 | 769 |
if (!is.null(modules)) { |
... | ... |
@@ -135,12 +135,17 @@ normalizeCounts <- function(counts, |
135 | 135 |
#' \code{from} and \code{to} arguments. |
136 | 136 |
#' @param sce \linkS4class{SingleCellExperiment} object returned from |
137 | 137 |
#' \link{celda_C} or \link{celda_CG}. Must contain column |
138 |
-#' \code{celda_cell_cluster} in \link[SummarizedExperiment]{colData}. |
|
138 |
+#' \code{celda_cell_cluster} in |
|
139 |
+#' \code{\link[SummarizedExperiment]{colData}(altExp(sce, altExpName))}. |
|
140 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
141 |
+#' to use. Default "featureSubset". |
|
139 | 142 |
#' @param from Numeric vector. Unique values in the range of |
140 |
-#' \code{seq(celdaClusters(sce))} that correspond to the original cluster |
|
143 |
+#' \code{seq(celdaClusters(sce, altExpName = altExpName))} that correspond to |
|
144 |
+#' the original cluster |
|
141 | 145 |
#' labels in \code{sce}. |
142 | 146 |
#' @param to Numeric vector. Unique values in the range of |
143 |
-#' \code{seq(celdaClusters(sce))} that correspond to the new cluster labels. |
|
147 |
+#' \code{seq(celdaClusters(sce, altExpName = altExpName))} that correspond to |
|
148 |
+#' the new cluster labels. |
|
144 | 149 |
#' @return \linkS4class{SingleCellExperiment} object with recoded cell |
145 | 150 |
#' cluster labels. |
146 | 151 |
#' @examples |
... | ... |
@@ -148,15 +153,16 @@ normalizeCounts <- function(counts, |
148 | 153 |
#' sceReorderedZ <- recodeClusterZ(sceCeldaCG, c(1, 3), c(3, 1)) |
149 | 154 |
#' @importFrom plyr mapvalues |
150 | 155 |
#' @export |
151 |
-recodeClusterZ <- function(sce, from, to) { |
|
156 |
+recodeClusterZ <- function(sce, altExpName = "featureSubset", from, to) { |
|
152 | 157 |
if (length(setdiff(from, to)) != 0) { |
153 | 158 |
stop("All values in 'from' must have a mapping in 'to'") |
154 | 159 |
} |
155 |
- if (is.null(celdaClusters(sce))) { |
|
160 |
+ if (is.null(celdaClusters(sce, altExpName = altExpName))) { |
|
156 | 161 |
stop("Provided 'sce' argument does not have a 'celda_cell_cluster'", |
157 |
- " column in 'colData(sce)'") |
|
162 |
+ " column in 'colData(altExp(sce, altExpName))'") |
|
158 | 163 |
} |
159 |
- celdaClusters(sce) <- plyr::mapvalues(celdaClusters(sce), from, to) |
|
164 |
+ celdaClusters(sce, altExpName = altExpName) <- plyr::mapvalues( |
|
165 |
+ celdaClusters(sce, altExpName = altExpName), from, to) |
|
160 | 166 |
return(sce) |
161 | 167 |
} |
162 | 168 |
|
... | ... |
@@ -180,7 +186,10 @@ recodeClusterZ <- function(sce, from, to) { |
180 | 186 |
#' \code{from} and \code{to} arguments. |
181 | 187 |
#' @param sce \linkS4class{SingleCellExperiment} object returned from |
182 | 188 |
#' \link{celda_G} or \link{celda_CG}. Must contain column |
183 |
-#' \code{celda_feature_module} in \link[SummarizedExperiment]{rowData}. |
|
189 |
+#' \code{celda_feature_module} in |
|
190 |
+#' \code{\link[SummarizedExperiment]{rowData}(altExp(sce, altExpName))}. |
|
191 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
192 |
+#' to use. Default "featureSubset". |
|
184 | 193 |
#' @param from Numeric vector. Unique values in the range of |
185 | 194 |
#' \code{seq(celdaModules(sce))} that correspond to the original module labels |
186 | 195 |
#' in \code{sce}. |
... | ... |
@@ -192,15 +201,16 @@ recodeClusterZ <- function(sce, from, to) { |
192 | 201 |
#' data(sceCeldaCG) |
193 | 202 |
#' sceReorderedY <- recodeClusterY(sceCeldaCG, c(1, 3), c(3, 1)) |
194 | 203 |
#' @export |
195 |
-recodeClusterY <- function(sce, from, to) { |
|
204 |
+recodeClusterY <- function(sce, altExpName = "featureSubset", from, to) { |
|
196 | 205 |
if (length(setdiff(from, to)) != 0) { |
197 | 206 |
stop("All values in 'from' must have a mapping in 'to'") |
198 | 207 |
} |
199 | 208 |
if (is.null(celdaModules(sce))) { |
200 | 209 |
stop("Provided 'sce' argument does not have a 'celda_feature_module'", |
201 |
- " column in 'rowData(sce)'") |
|
210 |
+ " column in 'rowData(altExp(sce, altExpName))'") |
|
202 | 211 |
} |
203 |
- celdaModules(sce) <- plyr::mapvalues(celdaModules(sce), from, to) |
|
212 |
+ celdaModules(sce, altExpName = altExpName) <- plyr::mapvalues( |
|
213 |
+ celdaModules(sce, altExpName = altExpName), from, to) |
|
204 | 214 |
return(sce) |
205 | 215 |
} |
206 | 216 |
|
... | ... |
@@ -452,6 +462,8 @@ distinctColors <- function(n, |
452 | 462 |
#' Rows represent features and columns represent cells. |
453 | 463 |
#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
454 | 464 |
#' slot to use. Default "counts". |
465 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
466 |
+#' to use. Default "featureSubset". |
|
455 | 467 |
#' @param outputFile File name for feature module table. If NULL, file will |
456 | 468 |
#' not be created. Default NULL. |
457 | 469 |
#' @return Matrix. Contains a list of features per each column (feature module) |
... | ... |
@@ -460,9 +472,11 @@ distinctColors <- function(n, |
460 | 472 |
#' featureModuleTable(sceCeldaCG) |
461 | 473 |
#' @importFrom stringi stri_list2matrix |
462 | 474 |
#' @export |
463 |
-featureModuleTable <- function(sce, useAssay = "counts", outputFile = NULL) { |
|
464 |
- factorize.matrix <- factorizeMatrix(sce, useAssay) |
|
465 |
- allGenes <- topRank(factorize.matrix$proportions$module, n = nrow(sce)) |
|
475 |
+featureModuleTable <- function(sce, useAssay = "counts", |
|
476 |
+ altExpName = "featureSubset", outputFile = NULL) { |
|
477 |
+ |
|
478 |
+ factorizeMatrix <- factorizeMatrix(sce, useAssay, altExpName = altExpName) |
|
479 |
+ allGenes <- topRank(factorizeMatrix$proportions$module, n = nrow(sce)) |
|
466 | 480 |
res <- as.data.frame(stringi::stri_list2matrix(allGenes$names)) |
467 | 481 |
res <- apply(res, c(1, 2), function(x) { |
468 | 482 |
if (is.na(x)) { |
... | ... |
@@ -523,7 +537,8 @@ featureModuleTable <- function(sce, useAssay = "counts", outputFile = NULL) { |
523 | 537 |
#' retrieveFeatureIndex(c("Gene_1", "Gene_5"), celdaCGSim$counts, |
524 | 538 |
#' exactMatch = FALSE) |
525 | 539 |
#' @export |
526 |
-retrieveFeatureIndex <- function(features, x, |
|
540 |
+retrieveFeatureIndex <- function(features, |
|
541 |
+ x, |
|
527 | 542 |
by = "rownames", |
528 | 543 |
exactMatch = TRUE, |
529 | 544 |
removeNA = FALSE) { |
... | ... |
@@ -5,6 +5,8 @@ |
5 | 5 |
#' returned by \link{celda_C}, \link{celda_G}, or \link{celda_CG}. |
6 | 6 |
#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
7 | 7 |
#' slot to use. Default "counts". |
8 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
9 |
+#' to use. Default "featureSubset". |
|
8 | 10 |
#' @param featureIx Integer vector. Select features for display in heatmap. If |
9 | 11 |
#' NULL, no subsetting will be performed. Default NULL. \strong{Only used for |
10 | 12 |
#' \code{sce} containing celda_C model result returned by \link{celda_C}.} |
... | ... |
@@ -28,27 +30,35 @@ setGeneric("celdaHeatmap", |
28 | 30 |
#' celdaHeatmap(sceCeldaCG) |
29 | 31 |
#' @export |
30 | 32 |
setMethod("celdaHeatmap", signature(sce = "SingleCellExperiment"), |
31 |
- function(sce, useAssay = "counts", featureIx = NULL, nfeatures = 25, ...) { |
|
32 |
- if (celdaModel(sce) == "celda_C") { |
|
33 |
+ function(sce, useAssay = "counts", altExpName = "featureSubset", |
|
34 |
+ featureIx = NULL, nfeatures = 25, ...) { |
|
35 |
+ |
|
36 |
+ aleExp <- SingleCellExperiment::altExp(sce, altExpName) |
|
37 |
+ |
|
38 |
+ if (celdaModel(aleExp) == "celda_C") { |
|
33 | 39 |
g <- .celdaHeatmapCelda_C(sce = sce, |
34 | 40 |
useAssay = useAssay, |
41 |
+ altExpName = altExpName, |
|
35 | 42 |
featureIx = featureIx, |
36 | 43 |
...) |
37 | 44 |
return(g) |
38 |
- } else if (celdaModel(sce) == "celda_CG") { |
|
45 |
+ } else if (celdaModel(aleExp) == "celda_CG") { |
|
39 | 46 |
g <- .celdaHeatmapCelda_CG(sce = sce, |
40 | 47 |
useAssay = useAssay, |
48 |
+ altExpName = altExpName, |
|
41 | 49 |
nfeatures = nfeatures, |
42 | 50 |
...) |
43 | 51 |
return(g) |
44 |
- } else if (celdaModel(sce) == "celda_G") { |
|
52 |
+ } else if (celdaModel(aleExp) == "celda_G") { |
|
45 | 53 |
g <- .celdaHeatmapCelda_G(sce = sce, |
46 | 54 |
useAssay = useAssay, |
55 |
+ altExpName = altExpName, |
|
47 | 56 |
nfeatures = nfeatures, |
48 | 57 |
...) |
49 | 58 |
return(g) |
50 | 59 |
} else { |
51 |
- stop("S4Vectors::metadata(sce)$celda_parameters$model must be", |
|
60 |
+ stop("S4Vectors::metadata(altExp(sce, altExpName))$", |
|
61 |
+ "celda_parameters$model must be", |
|
52 | 62 |
" one of 'celda_C', 'celda_G', or 'celda_CG'") |
53 | 63 |
} |
54 | 64 |
} |
... | ... |
@@ -56,7 +66,7 @@ setMethod("celdaHeatmap", signature(sce = "SingleCellExperiment"), |
56 | 66 |
|
57 | 67 |
|
58 | 68 |
.celdaHeatmapCelda_C <- function(sce, |
59 |
- useAssay, featureIx, ...) { |
|
69 |
+ useAssay, altExpName, featureIx, ...) { |
|
60 | 70 |
|
61 | 71 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
62 | 72 |
counts <- .processCounts(counts) |
... | ... |
@@ -66,42 +76,44 @@ setMethod("celdaHeatmap", signature(sce = "SingleCellExperiment"), |
66 | 76 |
|
67 | 77 |
if (is.null(featureIx)) { |
68 | 78 |
return(plotHeatmap(norm, |
69 |
- z = celdaClusters(sce), ...)) |
|
79 |
+ z = celdaClusters(sce, altExpName = altExpName), ...)) |
|
70 | 80 |
} |
71 | 81 |
|
72 | 82 |
return(plotHeatmap(norm[featureIx, ], |
73 |
- z = celdaClusters(sce), ...)) |
|
83 |
+ z = celdaClusters(sce, altExpName = altExpName), ...)) |
|
74 | 84 |
} |
75 | 85 |
|
76 | 86 |
|
77 |
-.celdaHeatmapCelda_CG <- function(sce, useAssay, nfeatures, ...) { |
|
87 |
+.celdaHeatmapCelda_CG <- function(sce, useAssay, altExpName, nfeatures, ...) { |
|
78 | 88 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
79 | 89 |
counts <- .processCounts(counts) |
80 |
- fm <- factorizeMatrix(x = sce, useAssay = useAssay, type = "proportion") |
|
90 |
+ fm <- factorizeMatrix(x = sce, useAssay = useAssay, |
|
91 |
+ altExpName = altExpName, type = "proportion") |
|
81 | 92 |
top <- topRank(fm$proportions$module, n = nfeatures) |
82 | 93 |
ix <- unlist(top$index) |
94 |
+ rn <- unlist(top$names) |
|
83 | 95 |
norm <- normalizeCounts(counts, |
84 | 96 |
normalize = "proportion", |
85 | 97 |
transformationFun = sqrt) |
86 |
- plt <- plotHeatmap(norm[ix, ], |
|
87 |
- z = celdaClusters(sce), |
|
98 |
+ plt <- plotHeatmap(norm[rn, ], |
|