... | ... |
@@ -18,6 +18,7 @@ export(celdaUmap) |
18 | 18 |
export(celda_C) |
19 | 19 |
export(celda_CG) |
20 | 20 |
export(celda_G) |
21 |
+export(celdatosce) |
|
21 | 22 |
export(clusterProbability) |
22 | 23 |
export(clusters) |
23 | 24 |
export(compareCountMatrix) |
... | ... |
@@ -67,6 +68,7 @@ export(sampleLabel) |
67 | 68 |
export(selectBestModel) |
68 | 69 |
export(simulateCells) |
69 | 70 |
export(simulateContamination) |
71 |
+export(subsetCeldaList) |
|
70 | 72 |
export(topRank) |
71 | 73 |
exportMethods("clusters<-") |
72 | 74 |
exportMethods("decontXcounts<-") |
... | ... |
@@ -83,6 +85,7 @@ exportMethods(celdaUmap) |
83 | 85 |
exportMethods(celda_C) |
84 | 86 |
exportMethods(celda_CG) |
85 | 87 |
exportMethods(celda_G) |
88 |
+exportMethods(celdatosce) |
|
86 | 89 |
exportMethods(clusterProbability) |
87 | 90 |
exportMethods(clusters) |
88 | 91 |
exportMethods(countChecksum) |
... | ... |
@@ -99,6 +102,7 @@ exportMethods(perplexity) |
99 | 102 |
exportMethods(resList) |
100 | 103 |
exportMethods(runParams) |
101 | 104 |
exportMethods(sampleLabel) |
105 |
+exportMethods(subsetCeldaList) |
|
102 | 106 |
import(Rcpp) |
103 | 107 |
import(RcppEigen) |
104 | 108 |
import(SummarizedExperiment) |
... | ... |
@@ -11,8 +11,17 @@ setClass( |
11 | 11 |
) # z and or y |
12 | 12 |
|
13 | 13 |
|
14 |
+setClass("celdaList", |
|
15 |
+ slots = c(runParams = "data.frame", |
|
16 |
+ resList = "list", |
|
17 |
+ countChecksum = "character", |
|
18 |
+ perplexity = "matrix", |
|
19 |
+ celdaGridSearchParameters = "list") |
|
20 |
+) |
|
21 |
+ |
|
22 |
+ |
|
14 | 23 |
#' @title Get or set the cell cluster labels from a celda |
15 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object or celda model |
|
24 |
+#' \linkS4class{SingleCellExperiment} object or celda model |
|
16 | 25 |
#' object. |
17 | 26 |
#' @description Return or set the cell cluster labels determined |
18 | 27 |
#' by \link{celda_C} or \link{celda_CG} models. |
... | ... |
@@ -80,7 +89,7 @@ setReplaceMethod("clusters", signature(x = "SingleCellExperiment"), |
80 | 89 |
|
81 | 90 |
|
82 | 91 |
#' @title Get or set the feature module labels from a celda |
83 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object. |
|
92 |
+#' \linkS4class{SingleCellExperiment} object. |
|
84 | 93 |
#' @description Return or set the feature module cluster labels determined |
85 | 94 |
#' by \link{celda_G} or \link{celda_CG} models. |
86 | 95 |
#' @param sce A \linkS4class{SingleCellExperiment} object returned by |
... | ... |
@@ -121,7 +130,7 @@ setReplaceMethod("modules", signature(sce = "SingleCellExperiment"), |
121 | 130 |
|
122 | 131 |
|
123 | 132 |
#' @title Get or set sample labels from a celda |
124 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object |
|
133 |
+#' \linkS4class{SingleCellExperiment} object |
|
125 | 134 |
#' @description Return or set the sample labels for the cells in \code{sce}. |
126 | 135 |
#' @param x Can be one of |
127 | 136 |
#' \itemize{ |
... | ... |
@@ -244,3 +253,96 @@ setMethod("matrixNames", |
244 | 253 |
celdaMod@names |
245 | 254 |
} |
246 | 255 |
) |
256 |
+ |
|
257 |
+ |
|
258 |
+#' @title Get run parameters from a celda model |
|
259 |
+#' \code{SingleCellExperiment} or \code{celdaList} object |
|
260 |
+#' @description Returns details on the clustering parameters and model |
|
261 |
+#' priors from the celdaList object when it was created. |
|
262 |
+#' @param x An object of class \linkS4class{SingleCellExperiment}. |
|
263 |
+#' @return Data Frame. Contains details on the various K/L parameters, chain |
|
264 |
+#' parameters, seed, and final log-likelihoods derived for each model in the |
|
265 |
+#' provided celdaList. |
|
266 |
+#' @export |
|
267 |
+setGeneric( |
|
268 |
+ "runParams", |
|
269 |
+ function(x) { |
|
270 |
+ standardGeneric("runParams") |
|
271 |
+ } |
|
272 |
+) |
|
273 |
+ |
|
274 |
+ |
|
275 |
+#' @examples |
|
276 |
+#' data(sceCeldaCGGridSearch) |
|
277 |
+#' runParams(sceCeldaCGGridSearch) |
|
278 |
+#' @rdname runParams |
|
279 |
+#' @export |
|
280 |
+setMethod("runParams", |
|
281 |
+ signature(x = "SingleCellExperiment"), |
|
282 |
+ function(x) { |
|
283 |
+ return(x@metadata$celda_grid_search@runParams) |
|
284 |
+ } |
|
285 |
+) |
|
286 |
+ |
|
287 |
+ |
|
288 |
+#' @title Get run parameters from a \code{celdaList} object |
|
289 |
+#' @description Returns details on the clustering parameters, and model priors |
|
290 |
+#' from the celdaList object when it was created. |
|
291 |
+#' @param x An object of class \code{celdaList}. |
|
292 |
+#' @return Data Frame. Contains details on the various K/L parameters, chain |
|
293 |
+#' parameters, seed, and final log-likelihoods derived for each model in the |
|
294 |
+#' provided celdaList. |
|
295 |
+#' @examples |
|
296 |
+#' data(celdaCGGridSearchRes) |
|
297 |
+#' runParams(celdaCGGridSearchRes) |
|
298 |
+#' @rdname runParams |
|
299 |
+#' @export |
|
300 |
+setMethod("runParams", |
|
301 |
+ signature(x = "celdaList"), |
|
302 |
+ function(x) { |
|
303 |
+ return(x@runParams) |
|
304 |
+ } |
|
305 |
+) |
|
306 |
+ |
|
307 |
+ |
|
308 |
+#' @title Get final celdaModels from a celda model \code{SCE} or celdaList |
|
309 |
+#' object |
|
310 |
+#' @description Returns all celda models generated during a |
|
311 |
+#' \link{celdaGridSearch} run. |
|
312 |
+#' @param x An object of class \linkS4class{SingleCellExperiment} or |
|
313 |
+#' \code{celdaList}. |
|
314 |
+#' @return List. Contains one celdaModel object for each of the parameters |
|
315 |
+#' specified in \code{runParams(x)}. |
|
316 |
+#' @export |
|
317 |
+setGeneric( |
|
318 |
+ "resList", |
|
319 |
+ function(x) { |
|
320 |
+ standardGeneric("resList") |
|
321 |
+ } |
|
322 |
+) |
|
323 |
+ |
|
324 |
+ |
|
325 |
+#' @examples |
|
326 |
+#' data(sceCeldaCGGridSearch) |
|
327 |
+#' celdaCGGridModels <- resList(sceCeldaCGGridSearch) |
|
328 |
+#' @rdname resList |
|
329 |
+#' @export |
|
330 |
+setMethod("resList", |
|
331 |
+ signature(x = "SingleCellExperiment"), |
|
332 |
+ function(x) { |
|
333 |
+ return(x@metadata$celda_grid_search@resList) |
|
334 |
+ } |
|
335 |
+) |
|
336 |
+ |
|
337 |
+ |
|
338 |
+#' @examples |
|
339 |
+#' data(celdaCGGridSearchRes) |
|
340 |
+#' celdaCGGridModels <- resList(celdaCGGridSearchRes) |
|
341 |
+#' @rdname resList |
|
342 |
+#' @export |
|
343 |
+setMethod("resList", |
|
344 |
+ signature(x = "celdaList"), |
|
345 |
+ function(x) { |
|
346 |
+ return(x@resList) |
|
347 |
+ } |
|
348 |
+) |
... | ... |
@@ -1,3 +1,29 @@ |
1 |
+#' @title Celda models |
|
2 |
+#' @description List of available Celda models with correpsonding descriptions. |
|
3 |
+#' @export |
|
4 |
+#' @examples |
|
5 |
+#' celda() |
|
6 |
+#' @return None |
|
7 |
+celda <- function() { |
|
8 |
+ message( |
|
9 |
+ "celda_C: Clusters the columns of a count matrix containing", |
|
10 |
+ " single-cell data into K subpopulations." |
|
11 |
+ ) |
|
12 |
+ message( |
|
13 |
+ "celda_G: Clusters the rows of a count matrix containing", |
|
14 |
+ " single-cell data into L modules." |
|
15 |
+ ) |
|
16 |
+ message( |
|
17 |
+ "celda_CG: Clusters the rows and columns of a count matrix", |
|
18 |
+ " containing single-cell data into L modules and K subpopulations,", |
|
19 |
+ " respectively." |
|
20 |
+ ) |
|
21 |
+ message( |
|
22 |
+ "celdaGridSearch: Run Celda with different combinations of", |
|
23 |
+ " parameters and multiple chains in parallel." |
|
24 |
+ ) |
|
25 |
+} |
|
26 |
+ |
|
1 | 27 |
|
2 | 28 |
#' @title Get log-likelihood history |
3 | 29 |
#' @description Retrieves the complete log-likelihood from all iterations of |
... | ... |
@@ -113,84 +139,6 @@ setClass("celda_G", contains = "celdaModel") |
113 | 139 |
|
114 | 140 |
setClass("celda_CG", contains = c("celda_C", "celda_G")) |
115 | 141 |
|
116 |
-setClass("celdaList", |
|
117 |
- slots = c(runParams = "data.frame", |
|
118 |
- resList = "list", |
|
119 |
- countChecksum = "character", |
|
120 |
- perplexity = "matrix", |
|
121 |
- celdaGridSearchParameters = "list") |
|
122 |
-) |
|
123 |
- |
|
124 |
- |
|
125 |
-#' @title Get run parameters provided to `celdaGridSearch()` |
|
126 |
-#' @description Returns details on the clustering parameters, and model priors |
|
127 |
-#' provided to `celdaGridSearch()` when the provided celdaList was |
|
128 |
-#' created. |
|
129 |
-#' @param celdaList An object of class celdaList. |
|
130 |
-#' @return Data Frame. Contains details on the various K/L parameters, chain |
|
131 |
-#' parameters, and final log-likelihoods derived for each model in the |
|
132 |
-#' provided celdaList. |
|
133 |
-#' @examples |
|
134 |
-#' data(celdaCGGridSearchRes) |
|
135 |
-#' runParams(celdaCGGridSearchRes) |
|
136 |
-#' @export |
|
137 |
-setGeneric( |
|
138 |
- "runParams", |
|
139 |
- function(celdaList) { |
|
140 |
- standardGeneric("runParams") |
|
141 |
- } |
|
142 |
-) |
|
143 |
-#' @title Get run parameters provided to `celdaGridSearch()` |
|
144 |
-#' @description Returns details on the clustering parameters, and model priors |
|
145 |
-#' provided to `celdaGridSearch()` when the provided celdaList was |
|
146 |
-#' created. |
|
147 |
-#' @param celdaList An object of class celdaList. |
|
148 |
-#' @return Data Frame. Contains details on the various K/L parameters, chain |
|
149 |
-#' parameters, and final log-likelihoods derived for each model in the |
|
150 |
-#' provided celdaList. |
|
151 |
-#' @examples |
|
152 |
-#' data(celdaCGGridSearchRes) |
|
153 |
-#' runParams(celdaCGGridSearchRes) |
|
154 |
-#' @export |
|
155 |
-setMethod("runParams", |
|
156 |
- signature = c(celdaList = "celdaList"), |
|
157 |
- function(celdaList) { |
|
158 |
- celdaList@runParams |
|
159 |
- } |
|
160 |
-) |
|
161 |
- |
|
162 |
- |
|
163 |
-#' @title Get final celdaModels from a celdaList |
|
164 |
-#' @description Returns all models generated during a `celdaGridSearch()` run. |
|
165 |
-#' @param celdaList An object of class celdaList. |
|
166 |
-#' @return List. Contains one celdaModel object for each of the parameters |
|
167 |
-#' specified in the `runParams()` of the provided celda list. |
|
168 |
-#' @examples |
|
169 |
-#' data(celdaCGGridSearchRes) |
|
170 |
-#' celdaCGGridModels <- resList(celdaCGGridSearchRes) |
|
171 |
-#' @export |
|
172 |
-setGeneric( |
|
173 |
- "resList", |
|
174 |
- function(celdaList) { |
|
175 |
- standardGeneric("resList") |
|
176 |
- } |
|
177 |
-) |
|
178 |
-#' @title Get final celdaModels from a celdaList |
|
179 |
-#' @description Returns all models generated during a `celdaGridSearch()` run. |
|
180 |
-#' @param celdaList An object of class celdaList. |
|
181 |
-#' @return List. Contains one celdaModel object for each of the parameters |
|
182 |
-#' specified in the `runParams()` of the provided celda list. |
|
183 |
-#' @examples |
|
184 |
-#' data(celdaCGGridSearchRes) |
|
185 |
-#' celdaCGGridModels <- resList(celdaCGGridSearchRes) |
|
186 |
-#' @export |
|
187 |
-setMethod("resList", |
|
188 |
- signature = c(celdaList = "celdaList"), |
|
189 |
- function(celdaList) { |
|
190 |
- celdaList@resList |
|
191 |
- } |
|
192 |
-) |
|
193 |
- |
|
194 | 142 |
|
195 | 143 |
#' @title Get perplexity for every model in a celdaList |
196 | 144 |
#' @description Returns perplexity for each model in a celdaList as calculated |
... | ... |
@@ -404,146 +404,139 @@ setMethod("celdaGridSearch", |
404 | 404 |
} |
405 | 405 |
|
406 | 406 |
|
407 |
-#' ################################################################################ |
|
408 |
-#' # Methods for manipulating celdaList objects # |
|
409 |
-#' ################################################################################ |
|
410 |
-#' #' @title Subset celda model from SCE object returned from |
|
411 |
-#' #' \code{celdaGridSearch} |
|
412 |
-#' #' @description Select a subset of models from a |
|
413 |
-#' #' \linkS4class{SingleCellExperiment} object generated by |
|
414 |
-#' #' \link{celdaGridSearch} that match the criteria in the argument |
|
415 |
-#' #' \code{params}. |
|
416 |
-#' #' @param x A \linkS4class{SingleCellExperiment} object returned from |
|
417 |
-#' #' \code{celdaGridSearch}. Must contain a list named |
|
418 |
-#' #' \code{"celda_grid_search"} in \code{metadata(x)}. |
|
419 |
-#' #' @param params List. List of parameters used to subset the matching celda |
|
420 |
-#' #' models in list \code{"celda_grid_search"} in \code{metadata(x)}. |
|
421 |
-#' #' @return A new \linkS4class{SingleCellExperiment} object containing |
|
422 |
-#' #' all models matching the |
|
423 |
-#' #' provided criteria in \code{params}. If only one celda model result in the |
|
424 |
-#' #' \code{"celda_grid_search"} slot in \code{metadata(x)} matches |
|
425 |
-#' #' the given criteria, a new \linkS4class{SingleCellExperiment} object |
|
426 |
-#' #' with the matching model stored in the |
|
427 |
-#' #' \link[S4Vectors]{metadata} |
|
428 |
-#' #' \code{"celda_parameters"} slot will be returned. Otherwise, a new |
|
429 |
-#' #' \linkS4class{SingleCellExperiment} object with the subset models stored |
|
430 |
-#' #' in the \link[S4Vectors]{metadata} |
|
431 |
-#' #' \code{"celda_grid_search"} slot will be returned. |
|
432 |
-#' #' @seealso \link{celdaGridSearch} can run Celda with multiple parameters and |
|
433 |
-#' #' chains in parallel. \link{selectBestModel} can get the best model for each |
|
434 |
-#' #' combination of parameters. |
|
435 |
-#' #' @examples |
|
436 |
-#' #' data(celdaCGGridSearchRes) |
|
437 |
-#' #' resK5L10 <- subsetCeldaList(celdaCGGridSearchRes, |
|
438 |
-#' #' params = list(K = 5, L = 10)) |
|
439 |
-#' #' @export |
|
440 |
-#' setGeneric("subsetCeldaList", function(x, ...) { |
|
441 |
-#' standardGeneric("subsetCeldaList")}) |
|
442 |
-#' |
|
443 |
-#' |
|
444 |
-#' #' @rdname subsetCeldaList |
|
445 |
-#' #' @export |
|
446 |
-#' setMethod("subsetCeldaList", |
|
447 |
-#' signature(x = "SingleCellExperiment"), |
|
448 |
-#' function(x, params) { |
|
449 |
-#' |
|
450 |
-#' ## Check for bad parameter names |
|
451 |
-#' if (!all(names(params) %in% colnames(runParams(celdaList)))) { |
|
452 |
-#' badParams <- setdiff(names(params), colnames(runParams(celdaList))) |
|
453 |
-#' stop( |
|
454 |
-#' "The following elements in 'params' are not columns in runParams", |
|
455 |
-#' " (celdaList) ", |
|
456 |
-#' paste(badParams, collapse = ",") |
|
457 |
-#' ) |
|
458 |
-#' } |
|
459 |
-#' |
|
460 |
-#' ## Subset 'runParams' based on items in 'params' |
|
461 |
-#' newRunParams <- runParams(celdaList) |
|
462 |
-#' for (i in names(params)) { |
|
463 |
-#' newRunParams <- |
|
464 |
-#' subset(newRunParams, newRunParams[, i] %in% params[[i]]) |
|
465 |
-#' |
|
466 |
-#' if (nrow(newRunParams) == 0) { |
|
467 |
-#' stop( |
|
468 |
-#' "No runs matched the criteria given in 'params'. Check", |
|
469 |
-#' " 'runParams(celdaList)' for complete list of parameters used", |
|
470 |
-#' " to generate 'celdaList'." |
|
471 |
-#' ) |
|
472 |
-#' } |
|
473 |
-#' } |
|
474 |
-#' |
|
475 |
-#' ## Get index of selected models, subset celdaList, and return |
|
476 |
-#' ix <- match(newRunParams$index, runParams(celdaList)$index) |
|
477 |
-#' if (length(ix) == 1) { |
|
478 |
-#' return(resList(celdaList)[[ix]]) |
|
479 |
-#' } else { |
|
480 |
-#' celdaList@runParams <- as.data.frame(newRunParams) |
|
481 |
-#' celdaList@resList <- resList(celdaList)[ix] |
|
482 |
-#' return(celdaList) |
|
483 |
-#' } |
|
484 |
-#' } |
|
407 |
+#' @title Subset celda model from SCE object returned from |
|
408 |
+#' \code{celdaGridSearch} |
|
409 |
+#' @description Select a subset of models from a |
|
410 |
+#' \linkS4class{SingleCellExperiment} object generated by |
|
411 |
+#' \link{celdaGridSearch} that match the criteria in the argument |
|
412 |
+#' \code{params}. |
|
413 |
+#' @param x Can be one of |
|
414 |
+#' \itemize{ |
|
415 |
+#' \item A \linkS4class{SingleCellExperiment} object returned from |
|
416 |
+#' \code{celdaGridSearch}. Must contain a list named |
|
417 |
+#' \code{"celda_grid_search"} in \code{metadata(x)}. |
|
418 |
+#' \item celdaList object.} |
|
419 |
+#' @param params List. List of parameters used to subset the matching celda |
|
420 |
+#' models in list \code{"celda_grid_search"} in \code{metadata(x)}. |
|
421 |
+#' @param useAssay A string specifying which \code{assay} |
|
422 |
+#' slot to use if \code{x} is a |
|
423 |
+#' \link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts". |
|
424 |
+#' @return One of |
|
425 |
+#' \itemize{ |
|
426 |
+#' \item A new \linkS4class{SingleCellExperiment} object containing |
|
427 |
+#' all models matching the |
|
428 |
+#' provided criteria in \code{params}. If only one celda model result in the |
|
429 |
+#' \code{"celda_grid_search"} slot in \code{metadata(x)} matches |
|
430 |
+#' the given criteria, a new \linkS4class{SingleCellExperiment} object |
|
431 |
+#' with the matching model stored in the |
|
432 |
+#' \link[S4Vectors]{metadata} |
|
433 |
+#' \code{"celda_parameters"} slot will be returned. Otherwise, a new |
|
434 |
+#' \linkS4class{SingleCellExperiment} object with the subset models stored |
|
435 |
+#' in the \link[S4Vectors]{metadata} |
|
436 |
+#' \code{"celda_grid_search"} slot will be returned. |
|
437 |
+#' \item A new \code{celdaList} object containing all models matching the |
|
438 |
+#' provided criteria in \code{params}. If only one item in the |
|
439 |
+#' \code{celdaList} matches the given criteria, the matching model will be |
|
440 |
+#' returned directly instead of a \code{celdaList} object.} |
|
441 |
+#' @seealso \link{celdaGridSearch} can run Celda with multiple parameters and |
|
442 |
+#' chains in parallel. \link{selectBestModel} can get the best model for each |
|
443 |
+#' combination of parameters. |
|
444 |
+#' @export |
|
445 |
+setGeneric("subsetCeldaList", function(x, ...) { |
|
446 |
+ standardGeneric("subsetCeldaList")}) |
|
485 | 447 |
|
486 | 448 |
|
487 |
-################################################################################ |
|
488 |
-# Methods for manipulating celdaList objects # |
|
489 |
-################################################################################ |
|
490 |
-#' @title Subset celdaList object from celdaGridSearch |
|
491 |
-#' @description Select a subset of models from a `celdaList` object generated |
|
492 |
-#' by `celdaGridSearch()` that match the criteria in the argument `params`. |
|
493 |
-#' @param x celdaList Object of class `celdaList`. An object |
|
494 |
-#' containing celda models returned from `celdaGridSearch` in older versions. |
|
495 |
-#' @param params List. List of parameters used to subset celdaList. |
|
496 |
-#' @return A new `celdaList` object containing all models matching the |
|
497 |
-#' provided criteria in `params`. If only one item in the `celdaList` matches |
|
498 |
-#' the given criteria, the matching model will be returned directly instead of |
|
499 |
-#' a `celdaList` object. |
|
500 |
-#' @seealso `celdaGridSearch()` can run Celda with multiple parameters and |
|
501 |
-#' chains in parallel. `selectBestModel()` can get the best model for each |
|
502 |
-#' combination of parameters. |
|
449 |
+#' @rdname subsetCeldaList |
|
503 | 450 |
#' @examples |
504 |
-#' data(celdaCGGridSearchRes) |
|
505 |
-#' resK5L10 <- .subsetCeldaList(celdaCGGridSearchRes, |
|
506 |
-#' params = list(K = 5, L = 10)) |
|
507 |
-subsetCeldaList <- function(celdaList, params) { |
|
508 |
- if (!methods::is(celdaList, "celdaList")) { |
|
509 |
- stop("celdaList parameter was not of class celdaList.") |
|
510 |
- } |
|
451 |
+#' data(sceCeldaCGGridSearch) |
|
452 |
+#' sceK5L10 <- subsetCeldaList(sceCeldaCGGridSearch, |
|
453 |
+#' params = list(K = 5, L = 10)) |
|
454 |
+#' @export |
|
455 |
+setMethod("subsetCeldaList", |
|
456 |
+ signature(x = "SingleCellExperiment"), |
|
457 |
+ function(x, params, useAssay = "counts") { |
|
458 |
+ |
|
459 |
+ ## Check for bad parameter names |
|
460 |
+ if (!all(names(params) %in% colnames(runParams(x)))) { |
|
461 |
+ badParams <- setdiff(names(params), colnames(runParams(x))) |
|
462 |
+ stop("The following elements in 'params' are not columns in", |
|
463 |
+ " runParams (x) ", |
|
464 |
+ paste(badParams, collapse = ",") |
|
465 |
+ ) |
|
466 |
+ } |
|
467 |
+ |
|
468 |
+ ## Subset 'runParams' based on items in 'params' |
|
469 |
+ newRunParams <- runParams(x) |
|
470 |
+ for (i in names(params)) { |
|
471 |
+ newRunParams <- |
|
472 |
+ subset(newRunParams, newRunParams[, i] %in% params[[i]]) |
|
473 |
+ |
|
474 |
+ if (nrow(newRunParams) == 0) { |
|
475 |
+ stop( |
|
476 |
+ "No runs matched the criteria given in 'params'. Check", |
|
477 |
+ " 'runParams(x)' for complete list of parameters used", |
|
478 |
+ " to generate 'x'." |
|
479 |
+ ) |
|
480 |
+ } |
|
481 |
+ } |
|
482 |
+ |
|
483 |
+ ## Get index of selected models, subset celdaList, and return |
|
484 |
+ ix <- match(newRunParams$index, runParams(x)$index) |
|
485 |
+ if (length(ix) == 1) { |
|
486 |
+ x <- celdatosce(resList(x)[[ix]], |
|
487 |
+ SummarizedExperiment::assay(x, i = useAssay)) |
|
488 |
+ } else { |
|
489 |
+ x@metadata$celda_grid_search@runParams <- |
|
490 |
+ as.data.frame(newRunParams) |
|
491 |
+ x@metadata$celda_grid_search@resList <- resList(x)[ix] |
|
492 |
+ } |
|
493 |
+ return(x) |
|
494 |
+ } |
|
495 |
+) |
|
511 | 496 |
|
512 |
- ## Check for bad parameter names |
|
513 |
- if (!all(names(params) %in% colnames(runParams(celdaList)))) { |
|
514 |
- badParams <- setdiff(names(params), colnames(runParams(celdaList))) |
|
515 |
- stop( |
|
516 |
- "The following elements in 'params' are not columns in runParams", |
|
517 |
- " (celdaList) ", |
|
518 |
- paste(badParams, collapse = ",") |
|
519 |
- ) |
|
520 |
- } |
|
521 | 497 |
|
522 |
- ## Subset 'runParams' based on items in 'params' |
|
523 |
- newRunParams <- runParams(celdaList) |
|
524 |
- for (i in names(params)) { |
|
525 |
- newRunParams <- |
|
526 |
- subset(newRunParams, newRunParams[, i] %in% params[[i]]) |
|
527 |
- |
|
528 |
- if (nrow(newRunParams) == 0) { |
|
529 |
- stop( |
|
530 |
- "No runs matched the criteria given in 'params'. Check", |
|
531 |
- " 'runParams(celdaList)' for complete list of parameters used", |
|
532 |
- " to generate 'celdaList'." |
|
533 |
- ) |
|
498 |
+#' @rdname subsetCeldaList |
|
499 |
+#' @examples |
|
500 |
+#' data(celdaCGGridSearchRes) |
|
501 |
+#' resK5L10 <- subsetCeldaList(celdaCGGridSearchRes, |
|
502 |
+#' params = list(K = 5, L = 10)) |
|
503 |
+#' @export |
|
504 |
+setMethod("subsetCeldaList", |
|
505 |
+ signature(x = "celdaList"), |
|
506 |
+ function(x, params) { |
|
507 |
+ ## Check for bad parameter names |
|
508 |
+ if (!all(names(params) %in% colnames(runParams(x)))) { |
|
509 |
+ badParams <- setdiff(names(params), colnames(runParams(x))) |
|
510 |
+ stop("The following elements in 'params' are not columns in", |
|
511 |
+ " runParams (x) ", |
|
512 |
+ paste(badParams, collapse = ",") |
|
513 |
+ ) |
|
514 |
+ } |
|
515 |
+ |
|
516 |
+ ## Subset 'runParams' based on items in 'params' |
|
517 |
+ newRunParams <- runParams(x) |
|
518 |
+ for (i in names(params)) { |
|
519 |
+ newRunParams <- |
|
520 |
+ subset(newRunParams, newRunParams[, i] %in% params[[i]]) |
|
521 |
+ |
|
522 |
+ if (nrow(newRunParams) == 0) { |
|
523 |
+ stop("No runs matched the criteria given in 'params'. Check", |
|
524 |
+ " 'runParams(x)' for complete list of parameters used", |
|
525 |
+ " to generate 'x'.") |
|
526 |
+ } |
|
527 |
+ } |
|
528 |
+ |
|
529 |
+ ## Get index of selected models, subset celdaList, and return |
|
530 |
+ ix <- match(newRunParams$index, runParams(x)$index) |
|
531 |
+ if (length(ix) == 1) { |
|
532 |
+ return(resList(x)[[ix]]) |
|
533 |
+ } else { |
|
534 |
+ x@runParams <- as.data.frame(newRunParams) |
|
535 |
+ x@resList <- resList(x)[ix] |
|
536 |
+ return(x) |
|
537 |
+ } |
|
534 | 538 |
} |
535 |
- } |
|
536 |
- |
|
537 |
- ## Get index of selected models, subset celdaList, and return |
|
538 |
- ix <- match(newRunParams$index, runParams(celdaList)$index) |
|
539 |
- if (length(ix) == 1) { |
|
540 |
- return(resList(celdaList)[[ix]]) |
|
541 |
- } else { |
|
542 |
- celdaList@runParams <- as.data.frame(newRunParams) |
|
543 |
- celdaList@resList <- resList(celdaList)[ix] |
|
544 |
- return(celdaList) |
|
545 |
- } |
|
546 |
-} |
|
539 |
+) |
|
547 | 540 |
|
548 | 541 |
|
549 | 542 |
#' @title Select best chain within each combination of parameters |
... | ... |
@@ -594,33 +587,6 @@ selectBestModel <- function(celdaList, asList = FALSE) { |
594 | 587 |
} |
595 | 588 |
|
596 | 589 |
|
597 |
-#' @title Celda models |
|
598 |
-#' @description List of available Celda models with correpsonding descriptions. |
|
599 |
-#' @export |
|
600 |
-#' @examples |
|
601 |
-#' celda() |
|
602 |
-#' @return None |
|
603 |
-celda <- function() { |
|
604 |
- message( |
|
605 |
- "celda_C: Clusters the columns of a count matrix containing", |
|
606 |
- " single-cell data into K subpopulations." |
|
607 |
- ) |
|
608 |
- message( |
|
609 |
- "celda_G: Clusters the rows of a count matrix containing", |
|
610 |
- " single-cell data into L modules." |
|
611 |
- ) |
|
612 |
- message( |
|
613 |
- "celda_CG: Clusters the rows and columns of a count matrix", |
|
614 |
- " containing single-cell data into L modules and K subpopulations,", |
|
615 |
- " respectively." |
|
616 |
- ) |
|
617 |
- message( |
|
618 |
- "celdaGridSearch: Run Celda with different combinations of", |
|
619 |
- " parameters and multiple chains in parallel." |
|
620 |
- ) |
|
621 |
-} |
|
622 |
- |
|
623 |
- |
|
624 | 590 |
.createSCEceldaGridSearch <- function(celdaList, |
625 | 591 |
sce, |
626 | 592 |
xClass, |
... | ... |
@@ -245,7 +245,6 @@ setMethod("celda_C", |
245 | 245 |
maxIter = maxIter, |
246 | 246 |
splitOnIter = splitOnIter, |
247 | 247 |
splitOnLast = splitOnLast, |
248 |
- seed = seed, |
|
249 | 248 |
nchains = nchains, |
250 | 249 |
zInitialize = zInitialize, |
251 | 250 |
zInit = zInit, |
... | ... |
@@ -1053,29 +1052,7 @@ setMethod("celda_C", |
1053 | 1052 |
.reorderCeldaC <- function(counts, res) { |
1054 | 1053 |
if (params(res)$K > 2 & isTRUE(length(unique(res@clusters$z)) > 1)) { |
1055 | 1054 |
res@clusters$z <- as.integer(as.factor(res@clusters$z)) |
1056 |
- |
|
1057 |
- xClass <- "matrix" |
|
1058 |
- useAssay <- NULL |
|
1059 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
1060 |
- assays = list(counts = counts)) |
|
1061 |
- |
|
1062 |
- sce <- .createSCEceldaC(celdaCMod = res, |
|
1063 |
- sce = sce, |
|
1064 |
- xClass = xClass, |
|
1065 |
- useAssay = useAssay, |
|
1066 |
- algorithm = NULL, |
|
1067 |
- stopIter = NULL, |
|
1068 |
- maxIter = NULL, |
|
1069 |
- splitOnIter = NULL, |
|
1070 |
- splitOnLast = NULL, |
|
1071 |
- seed = NULL, |
|
1072 |
- nchains = NULL, |
|
1073 |
- zInitialize = NULL, |
|
1074 |
- zInit = NULL, |
|
1075 |
- logfile = NULL, |
|
1076 |
- verbose = NULL) |
|
1077 |
- |
|
1078 |
- fm <- factorizeMatrix(sce, useAssay = "counts") |
|
1055 |
+ fm <- factorizeMatrix(counts, res) |
|
1079 | 1056 |
uniqueZ <- sort(unique(res@clusters$z)) |
1080 | 1057 |
d <- .cosineDist(fm$posterior$module[, uniqueZ]) |
1081 | 1058 |
h <- stats::hclust(d, method = "complete") |
... | ... |
@@ -1231,7 +1208,6 @@ setMethod("celda_C", |
1231 | 1208 |
maxIter, |
1232 | 1209 |
splitOnIter, |
1233 | 1210 |
splitOnLast, |
1234 |
- seed, |
|
1235 | 1211 |
nchains, |
1236 | 1212 |
zInitialize, |
1237 | 1213 |
zInit, |
... | ... |
@@ -1252,7 +1228,7 @@ setMethod("celda_C", |
1252 | 1228 |
maxIter = maxIter, |
1253 | 1229 |
splitOnIter = splitOnIter, |
1254 | 1230 |
splitOnLast = splitOnLast, |
1255 |
- seed = seed, |
|
1231 |
+ seed = celdaCMod@params$seed, |
|
1256 | 1232 |
nchains = nchains, |
1257 | 1233 |
zInitialize = zInitialize, |
1258 | 1234 |
countChecksum = celdaCMod@params$countChecksum, |
... | ... |
@@ -299,7 +299,6 @@ setMethod("celda_CG", |
299 | 299 |
maxIter = maxIter, |
300 | 300 |
splitOnIter = splitOnIter, |
301 | 301 |
splitOnLast = splitOnLast, |
302 |
- seed = seed, |
|
303 | 302 |
nchains = nchains, |
304 | 303 |
zInitialize = zInitialize, |
305 | 304 |
yInitialize = yInitialize, |
... | ... |
@@ -1319,34 +1318,10 @@ setMethod("celda_CG", |
1319 | 1318 |
|
1320 | 1319 |
|
1321 | 1320 |
.reorderCeldaCG <- function(counts, res) { |
1322 |
- |
|
1323 |
- xClass <- "matrix" |
|
1324 |
- useAssay <- NULL |
|
1325 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
1326 |
- assays = list(counts = counts)) |
|
1327 |
- |
|
1328 |
- sce <- .createSCEceldaCG(celdaCGMod = res, |
|
1329 |
- sce = sce, |
|
1330 |
- xClass = xClass, |
|
1331 |
- useAssay = useAssay, |
|
1332 |
- algorithm = NULL, |
|
1333 |
- stopIter = NULL, |
|
1334 |
- maxIter = NULL, |
|
1335 |
- splitOnIter = NULL, |
|
1336 |
- splitOnLast = NULL, |
|
1337 |
- seed = NULL, |
|
1338 |
- nchains = NULL, |
|
1339 |
- zInitialize = NULL, |
|
1340 |
- yInitialize = NULL, |
|
1341 |
- zInit = NULL, |
|
1342 |
- yInit = NULL, |
|
1343 |
- logfile = NULL, |
|
1344 |
- verbose = NULL) |
|
1345 |
- |
|
1346 | 1321 |
# Reorder K |
1347 | 1322 |
if (params(res)$K > 2 & isTRUE(length(unique(res@clusters$z)) > 1)) { |
1348 | 1323 |
res@clusters$z <- as.integer(as.factor(res@clusters$z)) |
1349 |
- fm <- factorizeMatrix(sce, useAssay = "counts", type = "posterior") |
|
1324 |
+ fm <- factorizeMatrix(counts, res, type = "posterior") |
|
1350 | 1325 |
uniqueZ <- sort(unique(res@clusters$z)) |
1351 | 1326 |
d <- .cosineDist(fm$posterior$cellPopulation[, uniqueZ]) |
1352 | 1327 |
h <- stats::hclust(d, method = "complete") |
... | ... |
@@ -1357,7 +1332,7 @@ setMethod("celda_CG", |
1357 | 1332 |
# Reorder L |
1358 | 1333 |
if (params(res)$L > 2 & isTRUE(length(unique(res@clusters$y)) > 1)) { |
1359 | 1334 |
res@clusters$y <- as.integer(as.factor(res@clusters$y)) |
1360 |
- fm <- factorizeMatrix(sce, useAssay = "counts", type = "posterior") |
|
1335 |
+ fm <- factorizeMatrix(counts, res, type = "posterior") |
|
1361 | 1336 |
uniqueY <- sort(unique(res@clusters$y)) |
1362 | 1337 |
cs <- prop.table(t(fm$posterior$cellPopulation[uniqueY, ]), 2) |
1363 | 1338 |
d <- .cosineDist(cs) |
... | ... |
@@ -1617,7 +1592,6 @@ setMethod("celda_CG", |
1617 | 1592 |
maxIter, |
1618 | 1593 |
splitOnIter, |
1619 | 1594 |
splitOnLast, |
1620 |
- seed, |
|
1621 | 1595 |
nchains, |
1622 | 1596 |
zInitialize, |
1623 | 1597 |
yInitialize, |
... | ... |
@@ -1643,7 +1617,7 @@ setMethod("celda_CG", |
1643 | 1617 |
maxIter = maxIter, |
1644 | 1618 |
splitOnIter = splitOnIter, |
1645 | 1619 |
splitOnLast = splitOnLast, |
1646 |
- seed = seed, |
|
1620 |
+ seed = celdaCGMod@params$seed, |
|
1647 | 1621 |
nchains = nchains, |
1648 | 1622 |
zInitialize = zInitialize, |
1649 | 1623 |
yInitialize = yInitialize, |
... | ... |
@@ -224,7 +224,6 @@ setMethod("celda_G", |
224 | 224 |
maxIter = maxIter, |
225 | 225 |
splitOnIter = splitOnIter, |
226 | 226 |
splitOnLast = splitOnLast, |
227 |
- seed = seed, |
|
228 | 227 |
nchains = nchains, |
229 | 228 |
yInitialize = yInitialize, |
230 | 229 |
yInit = yInit, |
... | ... |
@@ -1034,28 +1033,7 @@ setMethod("celda_G", |
1034 | 1033 |
.reorderCeldaG <- function(counts, res) { |
1035 | 1034 |
if (params(res)$L > 2 & isTRUE(length(unique(res@clusters$y)) > 1)) { |
1036 | 1035 |
res@clusters$y <- as.integer(as.factor(res@clusters$y)) |
1037 |
- |
|
1038 |
- xClass <- "matrix" |
|
1039 |
- useAssay <- NULL |
|
1040 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
1041 |
- assays = list(counts = counts)) |
|
1042 |
- |
|
1043 |
- sce <- .createSCEceldaG(celdaGMod = res, |
|
1044 |
- sce = sce, |
|
1045 |
- xClass = xClass, |
|
1046 |
- useAssay = useAssay, |
|
1047 |
- stopIter = NULL, |
|
1048 |
- maxIter = NULL, |
|
1049 |
- splitOnIter = NULL, |
|
1050 |
- splitOnLast = NULL, |
|
1051 |
- seed = NULL, |
|
1052 |
- nchains = NULL, |
|
1053 |
- yInitialize = NULL, |
|
1054 |
- yInit = NULL, |
|
1055 |
- logfile = NULL, |
|
1056 |
- verbose = NULL) |
|
1057 |
- |
|
1058 |
- fm <- factorizeMatrix(sce, useAssay = "counts") |
|
1036 |
+ fm <- factorizeMatrix(counts, res) |
|
1059 | 1037 |
uniqueY <- sort(unique(res@clusters$y)) |
1060 | 1038 |
cs <- prop.table(t(fm$posterior$cell[uniqueY, ]), 2) |
1061 | 1039 |
d <- .cosineDist(cs) |
... | ... |
@@ -1068,7 +1046,6 @@ setMethod("celda_G", |
1068 | 1046 |
|
1069 | 1047 |
.celdaHeatmapCelda_G <- function(sce, useAssay, nfeatures, ...) { |
1070 | 1048 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
1071 |
- |
|
1072 | 1049 |
fm <- factorizeMatrix(sce = sce, useAssay = useAssay, type = "proportion") |
1073 | 1050 |
top <- celda::topRank(fm$proportions$module, n = nfeatures) |
1074 | 1051 |
ix <- unlist(top$index) |
... | ... |
@@ -1126,7 +1103,6 @@ setMethod("celda_G", |
1126 | 1103 |
maxIter, |
1127 | 1104 |
splitOnIter, |
1128 | 1105 |
splitOnLast, |
1129 |
- seed, |
|
1130 | 1106 |
nchains, |
1131 | 1107 |
yInitialize, |
1132 | 1108 |
yInit, |
... | ... |
@@ -1146,7 +1122,7 @@ setMethod("celda_G", |
1146 | 1122 |
maxIter = maxIter, |
1147 | 1123 |
splitOnIter = splitOnIter, |
1148 | 1124 |
splitOnLast = splitOnLast, |
1149 |
- seed = seed, |
|
1125 |
+ seed = celdaGMod@params$seed, |
|
1150 | 1126 |
nchains = nchains, |
1151 | 1127 |
yInitialize = yInitialize, |
1152 | 1128 |
countChecksum = celdaGMod@params$countChecksum, |
... | ... |
@@ -257,6 +257,8 @@ compareCountMatrix <- function(counts, |
257 | 257 |
" the count matrix used to generate the provided celda result." |
258 | 258 |
) |
259 | 259 |
} else if (!res && !errorOnMismatch) { |
260 |
+ warning("There was a mismatch between the provided count matrix and", |
|
261 |
+ " the count matrix used to generate the provided celda result.") |
|
260 | 262 |
return(FALSE) |
261 | 263 |
} |
262 | 264 |
} |
263 | 265 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,126 @@ |
1 |
+ |
|
2 |
+#' @title Convert old celda model object to \code{SCE} object |
|
3 |
+#' @description Convert a old celda model object (\code{celda_C}, |
|
4 |
+#' \code{celda_G}, or \code{celda_CG} object) to a |
|
5 |
+#' \linkS4class{SingleCellExperiment} object containing celda model |
|
6 |
+#' information in \code{metadata} slot. Counts matrix is stored in the |
|
7 |
+#' \code{"counts"} assay slot in \code{assays}. |
|
8 |
+#' @param celdaModel A celda model object generated using older versions of |
|
9 |
+#' \code{celda}. |
|
10 |
+#' @param counts A numeric \link{matrix} of counts used to generate |
|
11 |
+#' \code{celdaModel}. Dimensions and MD5 checksum will be checked by |
|
12 |
+#' \link{compareCountMatrix}. |
|
13 |
+#' @return A \linkS4class{SingleCellExperiment} object. Function |
|
14 |
+#' parameter settings are stored in the \link[S4Vectors]{metadata} |
|
15 |
+#' \code{"celda_parameters"} slot. |
|
16 |
+#' Columns \code{celda_sample_label} and \code{celda_cell_cluster} in |
|
17 |
+#' \link[SummarizedExperiment]{colData} contain sample labels and celda cell |
|
18 |
+#' population clusters. Column \code{celda_feature_module} in |
|
19 |
+#' \link[SummarizedExperiment]{rowData} contain feature modules. |
|
20 |
+ |
|
21 |
+#' @export |
|
22 |
+setGeneric("celdatosce", function(celdaModel, counts) { |
|
23 |
+ standardGeneric("celdatosce")}) |
|
24 |
+ |
|
25 |
+ |
|
26 |
+#' @rdname celdatosce |
|
27 |
+#' @examples |
|
28 |
+#' data(celdaCMod, celdaCSim) |
|
29 |
+#' sce <- celdatosce(celdaCMod, celdaCSim$counts) |
|
30 |
+#' @export |
|
31 |
+setMethod("celdatosce", |
|
32 |
+ signature(celdaModel = "celda_C"), |
|
33 |
+ function(celdaModel, counts) { |
|
34 |
+ compareCountMatrix(counts, celdaModel, errorOnMismatch = FALSE) |
|
35 |
+ |
|
36 |
+ xClass <- "matrix" |
|
37 |
+ useAssay <- NULL |
|
38 |
+ sce <- SingleCellExperiment::SingleCellExperiment( |
|
39 |
+ assays = list(counts = counts)) |
|
40 |
+ |
|
41 |
+ sce <- .createSCEceldaC(celdaCMod = celdaModel, |
|
42 |
+ sce = sce, |
|
43 |
+ xClass = xClass, |
|
44 |
+ useAssay = useAssay, |
|
45 |
+ algorithm = NULL, |
|
46 |
+ stopIter = NULL, |
|
47 |
+ maxIter = NULL, |
|
48 |
+ splitOnIter = NULL, |
|
49 |
+ splitOnLast = NULL, |
|
50 |
+ nchains = NULL, |
|
51 |
+ zInitialize = NULL, |
|
52 |
+ zInit = NULL, |
|
53 |
+ logfile = NULL, |
|
54 |
+ verbose = NULL) |
|
55 |
+ return(sce) |
|
56 |
+ } |
|
57 |
+) |
|
58 |
+ |
|
59 |
+ |
|
60 |
+#' @rdname celdatosce |
|
61 |
+#' @examples |
|
62 |
+#' data(celdaGMod, celdaGSim) |
|
63 |
+#' sce <- celdatosce(celdaGMod, celdaGSim$counts) |
|
64 |
+#' @export |
|
65 |
+setMethod("celdatosce", |
|
66 |
+ signature(celdaModel = "celda_G"), |
|
67 |
+ function(celdaModel, counts) { |
|
68 |
+ compareCountMatrix(counts, celdaModel, errorOnMismatch = FALSE) |
|
69 |
+ |
|
70 |
+ xClass <- "matrix" |
|
71 |
+ useAssay <- NULL |
|
72 |
+ sce <- SingleCellExperiment::SingleCellExperiment( |
|
73 |
+ assays = list(counts = counts)) |
|
74 |
+ |
|
75 |
+ sce <- .createSCEceldaG(celdaGMod = celdaModel, |
|
76 |
+ sce = sce, |
|
77 |
+ xClass = xClass, |
|
78 |
+ useAssay = useAssay, |
|
79 |
+ stopIter = NULL, |
|
80 |
+ maxIter = NULL, |
|
81 |
+ splitOnIter = NULL, |
|
82 |
+ splitOnLast = NULL, |
|
83 |
+ nchains = NULL, |
|
84 |
+ yInitialize = NULL, |
|
85 |
+ yInit = NULL, |
|
86 |
+ logfile = NULL, |
|
87 |
+ verbose = NULL) |
|
88 |
+ return(sce) |
|
89 |
+ } |
|
90 |
+) |
|
91 |
+ |
|
92 |
+ |
|
93 |
+#' @rdname celdatosce |
|
94 |
+#' @examples |
|
95 |
+#' data(celdaCGMod, celdaCGSim) |
|
96 |
+#' sce <- celdatosce(celdaCGMod, celdaCGSim$counts) |
|
97 |
+#' @export |
|
98 |
+setMethod("celdatosce", |
|
99 |
+ signature(celdaModel = "celda_CG"), |
|
100 |
+ function(celdaModel, counts) { |
|
101 |
+ compareCountMatrix(counts, celdaModel, errorOnMismatch = FALSE) |
|
102 |
+ |
|
103 |
+ xClass <- "matrix" |
|
104 |
+ useAssay <- NULL |
|
105 |
+ sce <- SingleCellExperiment::SingleCellExperiment( |
|
106 |
+ assays = list(counts = counts)) |
|
107 |
+ |
|
108 |
+ sce <- .createSCEceldaCG(celdaCGMod = celdaModel, |
|
109 |
+ sce = sce, |
|
110 |
+ xClass = xClass, |
|
111 |
+ useAssay = useAssay, |
|
112 |
+ algorithm = NULL, |
|
113 |
+ stopIter = NULL, |
|
114 |
+ maxIter = NULL, |
|
115 |
+ splitOnIter = NULL, |
|
116 |
+ splitOnLast = NULL, |
|
117 |
+ nchains = NULL, |
|
118 |
+ zInitialize = NULL, |
|
119 |
+ yInitialize = NULL, |
|
120 |
+ zInit = NULL, |
|
121 |
+ yInit = NULL, |
|
122 |
+ logfile = NULL, |
|
123 |
+ verbose = NULL) |
|
124 |
+ return(sce) |
|
125 |
+ } |
|
126 |
+) |
6 | 6 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,49 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/celdatosce.R |
|
3 |
+\name{celdatosce} |
|
4 |
+\alias{celdatosce} |
|
5 |
+\alias{celdatosce,celda_C-method} |
|
6 |
+\alias{celdatosce,celda_G-method} |
|
7 |
+\alias{celdatosce,celda_CG-method} |
|
8 |
+\title{Convert old celda model object to \code{SCE} object} |
|
9 |
+\usage{ |
|
10 |
+celdatosce(celdaModel, counts) |
|
11 |
+ |
|
12 |
+\S4method{celdatosce}{celda_C}(celdaModel, counts) |
|
13 |
+ |
|
14 |
+\S4method{celdatosce}{celda_G}(celdaModel, counts) |
|
15 |
+ |
|
16 |
+\S4method{celdatosce}{celda_CG}(celdaModel, counts) |
|
17 |
+} |
|
18 |
+\arguments{ |
|
19 |
+\item{celdaModel}{A celda model object generated using older versions of |
|
20 |
+\code{celda}.} |
|
21 |
+ |
|
22 |
+\item{counts}{A numeric \link{matrix} of counts used to generate |
|
23 |
+\code{celdaModel}. Dimensions and MD5 checksum will be checked by |
|
24 |
+\link{compareCountMatrix}.} |
|
25 |
+} |
|
26 |
+\value{ |
|
27 |
+A \linkS4class{SingleCellExperiment} object. Function |
|
28 |
+ parameter settings are stored in the \link[S4Vectors]{metadata} |
|
29 |
+ \code{"celda_parameters"} slot. |
|
30 |
+ Columns \code{celda_sample_label} and \code{celda_cell_cluster} in |
|
31 |
+ \link[SummarizedExperiment]{colData} contain sample labels and celda cell |
|
32 |
+ population clusters. Column \code{celda_feature_module} in |
|
33 |
+ \link[SummarizedExperiment]{rowData} contain feature modules. |
|
34 |
+} |
|
35 |
+\description{ |
|
36 |
+Convert a old celda model object (\code{celda_C}, |
|
37 |
+ \code{celda_G}, or \code{celda_CG} object) to a |
|
38 |
+ \linkS4class{SingleCellExperiment} object containing celda model |
|
39 |
+ information in \code{metadata} slot. Counts matrix is stored in the |
|
40 |
+ \code{"counts"} assay slot in \code{assays}. |
|
41 |
+} |
|
42 |
+\examples{ |
|
43 |
+data(celdaCMod, celdaCSim) |
|
44 |
+sce <- celdatosce(celdaCMod, celdaCSim$counts) |
|
45 |
+data(celdaGMod, celdaGSim) |
|
46 |
+sce <- celdatosce(celdaGMod, celdaGSim$counts) |
|
47 |
+data(celdaCGMod, celdaCGSim) |
|
48 |
+sce <- celdatosce(celdaCGMod, celdaCGSim$counts) |
|
49 |
+} |
... | ... |
@@ -7,7 +7,7 @@ |
7 | 7 |
\alias{clusters<-} |
8 | 8 |
\alias{clusters<-,SingleCellExperiment-method} |
9 | 9 |
\title{Get or set the cell cluster labels from a celda |
10 |
- \link[SingleCellExperiment]{SingleCellExperiment} object or celda model |
|
10 |
+ \linkS4class{SingleCellExperiment} object or celda model |
|
11 | 11 |
object.} |
12 | 12 |
\usage{ |
13 | 13 |
clusters(x) |
... | ... |
@@ -6,7 +6,7 @@ |
6 | 6 |
\alias{modules<-} |
7 | 7 |
\alias{modules<-,SingleCellExperiment-method} |
8 | 8 |
\title{Get or set the feature module labels from a celda |
9 |
- \link[SingleCellExperiment]{SingleCellExperiment} object.} |
|
9 |
+ \linkS4class{SingleCellExperiment} object.} |
|
10 | 10 |
\usage{ |
11 | 11 |
modules(sce) |
12 | 12 |
|
13 | 13 |
deleted file mode 100644 |
... | ... |
@@ -1,22 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{resList,celdaList-method} |
|
4 |
-\alias{resList,celdaList-method} |
|
5 |
-\title{Get final celdaModels from a celdaList} |
|
6 |
-\usage{ |
|
7 |
-\S4method{resList}{celdaList}(celdaList) |
|
8 |
-} |
|
9 |
-\arguments{ |
|
10 |
-\item{celdaList}{An object of class celdaList.} |
|
11 |
-} |
|
12 |
-\value{ |
|
13 |
-List. Contains one celdaModel object for each of the parameters |
|
14 |
- specified in the `runParams()` of the provided celda list. |
|
15 |
-} |
|
16 |
-\description{ |
|
17 |
-Returns all models generated during a `celdaGridSearch()` run. |
|
18 |
-} |
|
19 |
-\examples{ |
|
20 |
-data(celdaCGGridSearchRes) |
|
21 |
-celdaCGGridModels <- resList(celdaCGGridSearchRes) |
|
22 |
-} |
... | ... |
@@ -1,22 +1,33 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 |
-% Please edit documentation in R/all_generics.R |
|
2 |
+% Please edit documentation in R/accessors.R |
|
3 | 3 |
\name{resList} |
4 | 4 |
\alias{resList} |
5 |
-\title{Get final celdaModels from a celdaList} |
|
5 |
+\alias{resList,SingleCellExperiment-method} |
|
6 |
+\alias{resList,celdaList-method} |
|
7 |
+\title{Get final celdaModels from a celda model \code{SCE} or celdaList |
|
8 |
+ object} |
|
6 | 9 |
\usage{ |
7 |
-resList(celdaList) |
|
10 |
+resList(x) |
|
11 |
+ |
|
12 |
+\S4method{resList}{SingleCellExperiment}(x) |
|
13 |
+ |
|
14 |
+\S4method{resList}{celdaList}(x) |
|
8 | 15 |
} |
9 | 16 |
\arguments{ |
10 |
-\item{celdaList}{An object of class celdaList.} |
|
17 |
+\item{x}{An object of class \linkS4class{SingleCellExperiment} or |
|
18 |
+\code{celdaList}.} |
|
11 | 19 |
} |
12 | 20 |
\value{ |
13 | 21 |
List. Contains one celdaModel object for each of the parameters |
14 |
- specified in the `runParams()` of the provided celda list. |
|
22 |
+ specified in \code{runParams(x)}. |
|
15 | 23 |
} |
16 | 24 |
\description{ |
17 |
-Returns all models generated during a `celdaGridSearch()` run. |
|
25 |
+Returns all celda models generated during a |
|
26 |
+ \link{celdaGridSearch} run. |
|
18 | 27 |
} |
19 | 28 |
\examples{ |
29 |
+data(sceCeldaCGGridSearch) |
|
30 |
+celdaCGGridModels <- resList(sceCeldaCGGridSearch) |
|
20 | 31 |
data(celdaCGGridSearchRes) |
21 | 32 |
celdaCGGridModels <- resList(celdaCGGridSearchRes) |
22 | 33 |
} |
23 | 34 |
deleted file mode 100644 |
... | ... |
@@ -1,25 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{runParams,celdaList-method} |
|
4 |
-\alias{runParams,celdaList-method} |
|
5 |
-\title{Get run parameters provided to `celdaGridSearch()`} |
|
6 |
-\usage{ |
|
7 |
-\S4method{runParams}{celdaList}(celdaList) |
|
8 |
-} |
|
9 |
-\arguments{ |
|
10 |
-\item{celdaList}{An object of class celdaList.} |
|
11 |
-} |
|
12 |
-\value{ |
|
13 |
-Data Frame. Contains details on the various K/L parameters, chain |
|
14 |
- parameters, and final log-likelihoods derived for each model in the |
|
15 |
- provided celdaList. |
|
16 |
-} |
|
17 |
-\description{ |
|
18 |
-Returns details on the clustering parameters, and model priors |
|
19 |
- provided to `celdaGridSearch()` when the provided celdaList was |
|
20 |
- created. |
|
21 |
-} |
|
22 |
-\examples{ |
|
23 |
-data(celdaCGGridSearchRes) |
|
24 |
-runParams(celdaCGGridSearchRes) |
|
25 |
-} |
... | ... |
@@ -1,25 +1,40 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 |
-% Please edit documentation in R/all_generics.R |
|
2 |
+% Please edit documentation in R/accessors.R |
|
3 | 3 |
\name{runParams} |
4 | 4 |
\alias{runParams} |
5 |
-\title{Get run parameters provided to `celdaGridSearch()`} |
|
5 |
+\alias{runParams,SingleCellExperiment-method} |
|
6 |
+\alias{runParams,celdaList-method} |
|
7 |
+\title{Get run parameters from a celda model |
|
8 |
+ \code{SingleCellExperiment} or \code{celdaList} object} |
|
6 | 9 |
\usage{ |
7 |
-runParams(celdaList) |
|
10 |
+runParams(x) |
|
11 |
+ |
|
12 |
+\S4method{runParams}{SingleCellExperiment}(x) |
|
13 |
+ |
|
14 |
+\S4method{runParams}{celdaList}(x) |
|
8 | 15 |
} |
9 | 16 |
\arguments{ |
10 |
-\item{celdaList}{An object of class celdaList.} |
|
17 |
+\item{x}{An object of class \code{celdaList}.} |
|
11 | 18 |
} |
12 | 19 |
\value{ |
13 | 20 |
Data Frame. Contains details on the various K/L parameters, chain |
14 |
- parameters, and final log-likelihoods derived for each model in the |
|
21 |
+ parameters, seed, and final log-likelihoods derived for each model in the |
|
22 |
+ provided celdaList. |
|
23 |
+ |
|
24 |
+Data Frame. Contains details on the various K/L parameters, chain |
|
25 |
+ parameters, seed, and final log-likelihoods derived for each model in the |
|
15 | 26 |
provided celdaList. |
16 | 27 |
} |
17 | 28 |
\description{ |
29 |
+Returns details on the clustering parameters and model |
|
30 |
+ priors from the celdaList object when it was created. |
|
31 |
+ |
|
18 | 32 |
Returns details on the clustering parameters, and model priors |
19 |
- provided to `celdaGridSearch()` when the provided celdaList was |
|
20 |
- created. |
|
33 |
+ from the celdaList object when it was created. |
|
21 | 34 |
} |
22 | 35 |
\examples{ |
36 |
+data(sceCeldaCGGridSearch) |
|
37 |
+runParams(sceCeldaCGGridSearch) |
|
23 | 38 |
data(celdaCGGridSearchRes) |
24 | 39 |
runParams(celdaCGGridSearchRes) |
25 | 40 |
} |
... | ... |
@@ -7,7 +7,7 @@ |
7 | 7 |
\alias{sampleLabel<-,SingleCellExperiment-method} |
8 | 8 |
\alias{sampleLabel,celdaModel-method} |
9 | 9 |
\title{Get or set sample labels from a celda |
10 |
- \link[SingleCellExperiment]{SingleCellExperiment} object} |
|
10 |
+ \linkS4class{SingleCellExperiment} object} |
|
11 | 11 |
\usage{ |
12 | 12 |
sampleLabel(x) |
13 | 13 |
|
... | ... |
@@ -2,36 +2,67 @@ |
2 | 2 |
% Please edit documentation in R/celdaGridSearch.R |
3 | 3 |
\name{subsetCeldaList} |
4 | 4 |
\alias{subsetCeldaList} |
5 |
-\title{Subset celdaList object from celdaGridSearch} |
|
5 |
+\alias{subsetCeldaList,SingleCellExperiment-method} |
|
6 |
+\alias{subsetCeldaList,celdaList-method} |
|
7 |
+\title{Subset celda model from SCE object returned from |
|
8 |
+ \code{celdaGridSearch}} |
|
6 | 9 |
\usage{ |
7 |
-subsetCeldaList(celdaList, params) |
|
10 |
+subsetCeldaList(x, ...) |
|
11 |
+ |
|
12 |
+\S4method{subsetCeldaList}{SingleCellExperiment}(x, params, useAssay = "counts") |
|
13 |
+ |
|
14 |
+\S4method{subsetCeldaList}{celdaList}(x, params) |
|
8 | 15 |
} |
9 | 16 |
\arguments{ |
10 |
-\item{params}{List. List of parameters used to subset celdaList.} |
|
17 |
+\item{x}{Can be one of |
|
18 |
+\itemize{ |
|
19 |
+ \item A \linkS4class{SingleCellExperiment} object returned from |
|
20 |
+ \code{celdaGridSearch}. Must contain a list named |
|
21 |
+ \code{"celda_grid_search"} in \code{metadata(x)}. |
|
22 |
+ \item celdaList object.}} |
|
23 |
+ |
|
24 |
+\item{params}{List. List of parameters used to subset the matching celda |
|
25 |
+models in list \code{"celda_grid_search"} in \code{metadata(x)}.} |
|
11 | 26 |
|
12 |
-\item{x}{celdaList Object of class `celdaList`. An object |
|
13 |
-containing celda models returned from `celdaGridSearch` in older versions.} |
|
27 |
+\item{useAssay}{A string specifying which \code{assay} |
|
28 |
+slot to use if \code{x} is a |
|
29 |
+\link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts".} |
|
14 | 30 |
} |
15 | 31 |
\value{ |
16 |
-A new `celdaList` object containing all models matching the |
|
17 |
- provided criteria in `params`. If only one item in the `celdaList` matches |
|
18 |
- the given criteria, the matching model will be returned directly instead of |
|
19 |
- a `celdaList` object. |
|
32 |
+One of |
|
33 |
+\itemize{ |
|
34 |
+ \item A new \linkS4class{SingleCellExperiment} object containing |
|
35 |
+ all models matching the |
|
36 |
+ provided criteria in \code{params}. If only one celda model result in the |
|
37 |
+ \code{"celda_grid_search"} slot in \code{metadata(x)} matches |
|
38 |
+ the given criteria, a new \linkS4class{SingleCellExperiment} object |
|
39 |
+ with the matching model stored in the |
|
40 |
+ \link[S4Vectors]{metadata} |
|
41 |
+ \code{"celda_parameters"} slot will be returned. Otherwise, a new |
|
42 |
+ \linkS4class{SingleCellExperiment} object with the subset models stored |
|
43 |
+ in the \link[S4Vectors]{metadata} |
|
44 |
+ \code{"celda_grid_search"} slot will be returned. |
|
45 |
+ \item A new \code{celdaList} object containing all models matching the |
|
46 |
+ provided criteria in \code{params}. If only one item in the |
|
47 |
+ \code{celdaList} matches the given criteria, the matching model will be |
|
48 |
+ returned directly instead of a \code{celdaList} object.} |
|
20 | 49 |
} |
21 | 50 |
\description{ |
22 |
-Select a subset of models from a `celdaList` object generated |
|
23 |
- by `celdaGridSearch()` that match the criteria in the argument `params`. |
|
24 |
-} |
|
25 |
-\details{ |
|
26 |
- |
|
51 |
+Select a subset of models from a |
|
52 |
+ \linkS4class{SingleCellExperiment} object generated by |
|
53 |
+ \link{celdaGridSearch} that match the criteria in the argument |
|
54 |
+ \code{params}. |
|
27 | 55 |
} |
28 | 56 |
\examples{ |
57 |
+data(sceCeldaCGGridSearch) |
|
58 |
+sceK5L10 <- subsetCeldaList(sceCeldaCGGridSearch, |
|
59 |
+ params = list(K = 5, L = 10)) |
|
29 | 60 |
data(celdaCGGridSearchRes) |
30 |
-resK5L10 <- .subsetCeldaList(celdaCGGridSearchRes, |
|
31 |
- params = list(K = 5, L = 10)) |
|
61 |
+resK5L10 <- subsetCeldaList(celdaCGGridSearchRes, |
|
62 |
+ params = list(K = 5, L = 10)) |
|
32 | 63 |
} |
33 | 64 |
\seealso{ |
34 |
-`celdaGridSearch()` can run Celda with multiple parameters and |
|
35 |
- chains in parallel. `selectBestModel()` can get the best model for each |
|
65 |
+\link{celdaGridSearch} can run Celda with multiple parameters and |
|
66 |
+ chains in parallel. \link{selectBestModel} can get the best model for each |
|
36 | 67 |
combination of parameters. |
37 | 68 |
} |