Former-commit-id: 94f44f1f921a841f0f899d6d5e48230596164cb0
... | ... |
@@ -1,35 +1,33 @@ |
1 | 1 |
# Generated by roxygen2: do not edit by hand |
2 | 2 |
|
3 |
+export() |
|
3 | 4 |
export(DeconX) |
4 | 5 |
export(available_models) |
5 | 6 |
export(celda) |
6 | 7 |
export(celdaGridSearch) |
7 | 8 |
export(celdaHeatmap) |
9 |
+export(celdaPerplexity) |
|
8 | 10 |
export(celdaProbabilityMap) |
9 | 11 |
export(celdaTsne) |
10 | 12 |
export(celda_C) |
11 | 13 |
export(celda_CG) |
12 | 14 |
export(celda_G) |
13 | 15 |
export(clusterProbability) |
14 |
-export(clustering) |
|
16 |
+export(clusters) |
|
15 | 17 |
export(compareCountMatrix) |
16 |
-export(completeLogLik) |
|
17 |
-export(countChecksum) |
|
18 | 18 |
export(differentialExpression) |
19 | 19 |
export(distinct_colors) |
20 | 20 |
export(factorizeMatrix) |
21 | 21 |
export(featureModuleLookup) |
22 |
-export(finalLogLik) |
|
23 |
-export(getPerplexity) |
|
24 |
-export(initialSeed) |
|
25 | 22 |
export(logLikelihood) |
26 | 23 |
export(logLikelihood.celda_C) |
27 | 24 |
export(logLikelihood.celda_CG) |
28 | 25 |
export(logLikelihood.celda_G) |
26 |
+export(logLikelihoodHistory) |
|
29 | 27 |
export(matrixNames) |
30 |
-export(modelPriors) |
|
31 | 28 |
export(moduleHeatmap) |
32 | 29 |
export(normalizeCounts) |
30 |
+export(params) |
|
33 | 31 |
export(perplexity) |
34 | 32 |
export(plotDimReduceCluster) |
35 | 33 |
export(plotDimReduceFeature) |
... | ... |
@@ -77,17 +77,17 @@ moduleHeatmap <- function(counts, celda.mod, feature.module = 1, top.cells = 100 |
77 | 77 |
cell_ix = match(colnames(filtered_norm.counts), celda.mod@names$column) |
78 | 78 |
z.to.plot = c() |
79 | 79 |
if(methods::.hasSlot(celda.mod, "z")){ |
80 |
- cell <- distinct_colors(length(unique(celda.mod@clustering$z)))[sort(unique(celda.mod@clustering$z[cell_ix]))] |
|
81 |
- names(cell) <- sort(unique(celda.mod@clustering$z[cell_ix])) |
|
80 |
+ cell <- distinct_colors(length(unique(celda.mod@clusters$z)))[sort(unique(celda.mod@clusters$z[cell_ix]))] |
|
81 |
+ names(cell) <- sort(unique(celda.mod@clusters$z[cell_ix])) |
|
82 | 82 |
anno_cell_colors <- list(cell = cell) |
83 |
- z.to.plot = celda.mod@clustering$z[cell.indices] |
|
83 |
+ z.to.plot = celda.mod@clusters$z[cell.indices] |
|
84 | 84 |
}else{ |
85 | 85 |
anno_cell_colors <- NULL |
86 | 86 |
} |
87 | 87 |
plotHeatmap( |
88 | 88 |
filtered_norm.counts, |
89 | 89 |
z = z.to.plot, |
90 |
- y = celda.mod@clustering$y[gene_ix], |
|
90 |
+ y = celda.mod@clusters$y[gene_ix], |
|
91 | 91 |
scale.row = scale.row, |
92 | 92 |
color.scheme = "divergent", |
93 | 93 |
show.names.feature = show_featurenames, |
... | ... |
@@ -1,108 +1,23 @@ |
1 | 1 |
setClass("celdaModel", |
2 |
- representation(completeLogLik = "numeric", |
|
3 |
- finalLogLik = "numeric", |
|
4 |
- seed = "numeric", |
|
5 |
- count.checksum = "character", |
|
2 |
+ representation(params = "list", # K, L, model priors, seed, checksum |
|
6 | 3 |
names = "list", |
7 |
- clustering = "list", # K, L, z, y, etc. |
|
8 |
- modelPriors = "list")) # alpha, beta, delta, etc. |
|
9 |
- |
|
10 |
-#' @title Get log-likelihood history |
|
11 |
-#' @description Retrieves the complete log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
12 |
-#' |
|
13 |
-#' @return Numeric. The log-likelihood at each step of Gibbs sampling used to generate the model. |
|
14 |
-#' @examples |
|
15 |
-#' completeLogLik(celda.CG.mod) |
|
16 |
-#' @export |
|
17 |
-setGeneric("completeLogLik", |
|
18 |
- function(celda.mod){ standardGeneric("completeLogLik") }) |
|
19 |
-setMethod("completeLogLik", |
|
20 |
- signature=c(celda.mod="celdaModel"), |
|
21 |
- function(celda.mod){ celda.mod@completeLogLik }) |
|
22 |
- |
|
23 |
-# @title Set log-likelihood history on a celda model |
|
24 |
-# @description Set the complete log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
25 |
-# @return A celdaModel object. The provided input object, with the updated completeLogLik property. |
|
26 |
-# @examples |
|
27 |
-# completeLogLik(celda.CG.mod) = c(0.00, 0.01, 0.02) # Lenth must match num.iter |
|
28 |
-#@export |
|
29 |
-# setGeneric("completeLogLik<-", |
|
30 |
-# function(celda.mod, value){ standardGeneric("completeLogLik<-") }) |
|
31 |
-# setReplaceMethod("completeLogLik", "celdaModel", |
|
32 |
-# function(celda.mod, value){ |
|
33 |
-# celda.mod@completeLogLik = value |
|
34 |
-# celda.mod |
|
35 |
-# }) |
|
4 |
+ completeLogLik = "numeric", |
|
5 |
+ finalLogLik = "numeric", |
|
6 |
+ clusters = "list")) # z and or y |
|
36 | 7 |
|
37 | 8 |
|
38 |
-#' @title Get final log-likelihood |
|
39 |
-#' @description Retrieves the final log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
40 |
-#' |
|
41 |
-#' @return Numeric. The log-likelihood at the final step of Gibbs sampling used to generate the model. |
|
9 |
+#' @title Get parameter values provided for celda model creation |
|
10 |
+#' @description Retrieves the K/L, model priors (e.g. alpha, beta), random seed, and count matrix checksum parameters provided during the creation of the provided celda model. |
|
11 |
+#' @return List. Contains the model-specific parameters for the provided celda model object depending on its class. |
|
42 | 12 |
#' @examples |
43 |
-#' finalLogLik(celda.CG.mod) |
|
13 |
+#' params(celda.CG.mod) |
|
44 | 14 |
#' @export |
45 |
-setGeneric("finalLogLik", |
|
46 |
- function(celda.mod){ standardGeneric("finalLogLik") }) |
|
47 |
-setMethod("finalLogLik", |
|
48 |
- signature=c(celda.mod="celdaModel"), |
|
49 |
- function(celda.mod){ celda.mod@finalLogLik }) |
|
15 |
+setGeneric("params", |
|
16 |
+ function(celda.mod){ standardGeneric("params") }) |
|
17 |
+setMethod("params", |
|
18 |
+ signature=c(celda.mod="celdaModel"), |
|
19 |
+ function(celda.mod){ celda.mod@params }) |
|
50 | 20 |
|
51 |
-# @title Set log-likelihood history on a celda model |
|
52 |
-# @description Set the final log-likelihood of Gibbs sampling used to generate a celda model. |
|
53 |
-# @return A celdaModel object. The provided input object, with the updated completeLogLik property. |
|
54 |
-# @examples |
|
55 |
-# finalLogLik(celda.CG.mod) = 0.97 |
|
56 |
-#@export |
|
57 |
-# setGeneric("finalLogLik<-", |
|
58 |
-# function(celda.mod, value){ standardGeneric("finalLogLik<-") }) |
|
59 |
-# setReplaceMethod("finalLogLik", "celdaModel", |
|
60 |
-# function(celda.mod, value){ |
|
61 |
-# celda.mod@finalLogLik = value |
|
62 |
-# celda.mod |
|
63 |
-# }) |
|
64 |
- |
|
65 |
- |
|
66 |
-#' @title Get seed used to generate model |
|
67 |
-#' @description Retrieves the random seed used to generate a celda model. |
|
68 |
-#' @return Numeric. The random seed used to generate the provided celda model. |
|
69 |
-#' @examples |
|
70 |
-#' initialSeed(celda.CG.mod) |
|
71 |
-#' @export |
|
72 |
-setGeneric("initialSeed", |
|
73 |
- function(celda.mod){ standardGeneric("initialSeed") }) |
|
74 |
-setMethod("initialSeed", |
|
75 |
- signature=c(celda.mod="celdaModel"), |
|
76 |
- function(celda.mod){ celda.mod@seed }) |
|
77 |
-#@export |
|
78 |
-# setGeneric("initialSeed<-", |
|
79 |
-# function(celda.mod, value){ standardGeneric("initialSeed<-") }) |
|
80 |
-# setReplaceMethod("initialSeed", "celdaModel", |
|
81 |
-# function(celda.mod, value){ |
|
82 |
-# celda.mod@seed = value |
|
83 |
-# celda.mod |
|
84 |
-# }) |
|
85 |
- |
|
86 |
- |
|
87 |
-#' @title Get count matrix checksum for comparison |
|
88 |
-#' @description Retrieves the MD5 checksum of the count matrix used to generate the provided celda mdoel. |
|
89 |
-#' @return Character. The MD5 hash of the count matrix used to generate the provided celda model. |
|
90 |
-#' @examples |
|
91 |
-#' countChecksum(celda.CG.mod) |
|
92 |
-#' @export |
|
93 |
-setGeneric("countChecksum", |
|
94 |
- function(celda.mod){ standardGeneric("countChecksum") }) |
|
95 |
-setMethod("countChecksum", |
|
96 |
- signature=c(celda.mod="celdaModel"), |
|
97 |
- function(celda.mod){ celda.mod@count.checksum }) |
|
98 |
-#@export |
|
99 |
-# setGeneric("countChecksum<-", |
|
100 |
-# function(celda.mod, value){ standardGeneric("countChecksum<-") }) |
|
101 |
-# setReplaceMethod("countChecksum", "celdaModel", |
|
102 |
-# function(celda.mod, value){ |
|
103 |
-# celda.mod@count.checksum = value |
|
104 |
-# celda.mod |
|
105 |
-# }) |
|
106 | 21 |
|
107 | 22 |
#' @title Get feature, cell and sample names from a celda model |
108 | 23 |
#' @description Retrieves the row, column, and sample names used to generate a celda model. |
... | ... |
@@ -113,78 +28,57 @@ setMethod("countChecksum", |
113 | 28 |
setGeneric("matrixNames", |
114 | 29 |
function(celda.mod){ standardGeneric("matrixNames") }) |
115 | 30 |
setMethod("matrixNames", |
116 |
- signature=c(celda.mod="celdaModel"), |
|
117 |
-#@export |
|
118 |
-# setGeneric("matrixNames<-", |
|
119 |
-# function(celda.mod, value){ standardGeneric("matrixNames<-") }) |
|
31 |
+ signature=c(celda.mod="celdaModel"), |
|
120 | 32 |
function(celda.mod){ celda.mod@names }) |
121 |
-# setReplaceMethod("matrixNames", "celdaModel", |
|
122 |
-# function(celda.mod, value){ |
|
123 |
-# celda.mod@names = value |
|
124 |
-# celda.mod |
|
125 |
-# }) |
|
126 | 33 |
|
127 | 34 |
|
128 |
-#' @title Get clustering parameters and outcomes from a celda model. |
|
129 |
-#' @description Returns the K/L parameters provided for modeling, as well as the corresponding z/y results. |
|
130 |
-#' @return List. Contains K, z (for celda_C and celda_CG models), and/or L, y (for celda_G and celda_CG models.) |
|
35 |
+#' @title Get log-likelihood history |
|
36 |
+#' @description Retrieves the complete log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
37 |
+#' |
|
38 |
+#' @return Numeric. The log-likelihood at each step of Gibbs sampling used to generate the model. |
|
131 | 39 |
#' @examples |
132 |
-#' clustering(celda.CG.mod) |
|
40 |
+#' logLikelihoodHistory(celda.CG.mod) |
|
133 | 41 |
#' @export |
134 |
-setGeneric("clustering", |
|
135 |
- function(celda.mod){ standardGeneric("clustering")}) |
|
136 |
-setMethod("clustering", signature=c(celda.mod="celdaModel"), |
|
137 |
- function(celda.mod){ |
|
138 |
- return(celda.mod@clustering) |
|
139 |
- }) |
|
140 |
-#@export |
|
141 |
-# setGeneric("clustering<-", |
|
142 |
-# function(celda.mod, value){ standardGeneric("clustering<-") }) |
|
42 |
+setGeneric("logLikelihoodHistory", |
|
43 |
+ function(celda.mod){ standardGeneric("logLikelihoodHistory") }) |
|
44 |
+setMethod("logLikelihoodHistory", |
|
45 |
+ signature=c(celda.mod="celdaModel"), |
|
46 |
+ function(celda.mod){ celda.mod@completeLogLik }) |
|
143 | 47 |
|
144 | 48 |
|
145 |
-#' @title Get model prior parameters from a celda model. |
|
146 |
-#' @description Returns the model priors (e.g. alpha, beta) provided at model creation for a given celda model. |
|
147 |
-#' @return List. Contains alpha, beta (for celda_C and celda_CG models), or delta, gamma (for celda_G and celda_CG models). |
|
49 |
+#' @title Get final log-likelihood |
|
50 |
+#' @description Retrieves the final log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
51 |
+#' @return Numeric. The log-likelihood at the final step of Gibbs sampling used to generate the model. |
|
148 | 52 |
#' @examples |
149 |
-#' modelPriors(celda.CG.mod) |
|
53 |
+#' logLikelihood(celda.CG.mod) |
|
54 |
+#' @export |
|
55 |
+setGeneric("logLikelihood", |
|
56 |
+ function(celda.mod){ standardGeneric("logLikelihood") }) |
|
57 |
+setMethod("logLikelihood", |
|
58 |
+ signature=c(celda.mod="celdaModel"), |
|
59 |
+ function(celda.mod){ celda.mod@finalLogLik }) |
|
60 |
+ |
|
61 |
+ |
|
62 |
+#' @title Get clustering outcomes from a celda model |
|
63 |
+#' @description Returns the z / y results corresponding to the cell / gene cluster labels determined by the provided celda model. |
|
64 |
+#' @return List. Contains z (for celda_C and celda_CG models) and/or y (for celda_G and celda_CG models) |
|
65 |
+#' @examples |
|
66 |
+#' clusters(celda.CG.mod) |
|
150 | 67 |
#' @export |
151 |
-setGeneric("modelPriors", |
|
152 |
- function(celda.mod){ standardGeneric("modelPriors")}) |
|
153 |
-setMethod("modelPriors", signature=c(celda.mod="celdaModel"), |
|
68 |
+setGeneric("clusters", |
|
69 |
+ function(celda.mod){ standardGeneric("clusters")}) |
|
70 |
+setMethod("clusters", signature=c(celda.mod="celdaModel"), |
|
154 | 71 |
function(celda.mod){ |
155 |
- return(celda.mod@modelPriors) |
|
72 |
+ return(celda.mod@clusters) |
|
156 | 73 |
}) |
157 |
-#@export |
|
158 |
-# setGeneric("modelPriors<-", |
|
159 |
-# function(celda.mod, value){ standardGeneric("modelPriors<-") }) |
|
160 | 74 |
|
161 | 75 |
|
162 | 76 |
setClass("celda_C", |
163 | 77 |
representation(sample.label = "factor"), |
164 | 78 |
contains = "celdaModel") |
165 |
-# setReplaceMethod("clustering", "celda_C", |
|
166 |
-# function(celda.mod, value){ |
|
167 |
-# lapply(names(value), |
|
168 |
-# function(key) { |
|
169 |
-# if (!is.element(key, c("K", "z"))) { |
|
170 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
171 |
-# } |
|
172 |
-# celda.mod@clustering[[key]] = value[[key]] |
|
173 |
-# }) |
|
174 |
-# }) |
|
175 |
-# setReplaceMethod("modelPriors", "celda_C", |
|
176 |
-# function(celda.mod, value){ |
|
177 |
-# lapply(names(value), |
|
178 |
-# function(key) { |
|
179 |
-# if (!is.element(key, c("alpha", "beta"))) { |
|
180 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
181 |
-# } |
|
182 |
-# celda.mod@modelPriors[[key]] = value[[key]] |
|
183 |
-# }) |
|
184 |
-# }) |
|
185 |
- |
|
186 |
- |
|
187 |
-#' @title Get sample labels |
|
79 |
+ |
|
80 |
+ |
|
81 |
+#' @title Get sample labels from a celda model |
|
188 | 82 |
#' @description Returns the sample labels for the count matrix provided for generation of a given celda model. |
189 | 83 |
#' @return Character. Contains the sample labels provided at model creation time, or those automatically generated by celda. |
190 | 84 |
#' @examples |
... | ... |
@@ -195,65 +89,13 @@ setGeneric("sampleLabel", |
195 | 89 |
setMethod("sampleLabel", |
196 | 90 |
signature=c(celda.mod="celdaModel"), |
197 | 91 |
function(celda.mod){ celda.mod@sample.label }) |
198 |
-#@export |
|
199 |
-# setGeneric("sampleLabel<-", |
|
200 |
-# function(celda.mod, value){ standardGeneric("sampleLabel<-") }) |
|
201 |
-# setReplaceMethod("sampleLabel", "celdaModel", |
|
202 |
-# function(celda.mod, value){ |
|
203 |
-# celda.mod@sample.label = value |
|
204 |
-# celda.mod |
|
205 |
-# }) |
|
206 | 92 |
|
207 | 93 |
|
208 | 94 |
setClass("celda_G", |
209 | 95 |
contains = "celdaModel") |
210 |
-# setReplaceMethod("clustering", "celda_G", |
|
211 |
-# function(celda.mod, value){ |
|
212 |
-# lapply(names(value), |
|
213 |
-# function(key) { |
|
214 |
-# if (!is.element(key, c("L", "y"))) { |
|
215 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
216 |
-# } |
|
217 |
-# celda.mod@clustering[[key]] = value[[key]] |
|
218 |
-# }) |
|
219 |
-# }) |
|
220 |
-# setReplaceMethod("modelPriors", "celda_G", |
|
221 |
-# function(celda.mod, value){ |
|
222 |
-# lapply(names(value), |
|
223 |
-# function(key) { |
|
224 |
-# if (!is.element(key, c("beta", "delta", "gamma"))) { |
|
225 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
226 |
-# } |
|
227 |
-# celda.mod@modelPriors[[key]] = value[[key]] |
|
228 |
-# }) |
|
229 |
-# }) |
|
230 |
- |
|
231 | 96 |
|
232 | 97 |
setClass("celda_CG", |
233 | 98 |
contains = c("celda_C", "celda_G")) |
234 |
-# setReplaceMethod("clustering", "celda_CG", |
|
235 |
-# function(celda.mod, value){ |
|
236 |
-# lapply(names(value), |
|
237 |
-# function(key) { |
|
238 |
-# if (!is.element(key, c("K", "L", "y", "z"))) { |
|
239 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
240 |
-# } |
|
241 |
-# celda.mod@clustering[[key]] = value[[key]] |
|
242 |
-# }) |
|
243 |
-# }) |
|
244 |
-# setReplaceMethod("modelPriors", "celda_CG", |
|
245 |
-# function(celda.mod, value){ |
|
246 |
-# lapply(names(value), |
|
247 |
-# function(key) { |
|
248 |
-# if (!is.element(key, c("alpha", "beta", "delta", "gamma"))) { |
|
249 |
-# stop(paste0("Invalid parameter provided: ", key)) |
|
250 |
-# } |
|
251 |
-# celda.mod@modelPriors[[key]] = value[[key]] |
|
252 |
-# }) |
|
253 |
-# }) |
|
254 |
- |
|
255 |
- |
|
256 |
- |
|
257 | 99 |
|
258 | 100 |
setClass("celdaList", |
259 | 101 |
representation(run.params = "data.frame", |
... | ... |
@@ -261,6 +103,7 @@ setClass("celdaList", |
261 | 103 |
count.checksum = "character", |
262 | 104 |
perplexity = "matrix")) |
263 | 105 |
|
106 |
+ |
|
264 | 107 |
#' @title Get run parameters provided to `celdaGridSearch()` |
265 | 108 |
#' @description Returns details on the clustering parameters, model priors, and seeds provided to `celdaGridSearch()` when the provided celdaList was created. |
266 | 109 |
#' @return Data Frame. Contains details on the various K/L parameters, chain parameters, and final log-likelihoods derived for each model in the provided celdaList. |
... | ... |
@@ -272,14 +115,7 @@ setGeneric("runParams", |
272 | 115 |
setMethod("runParams", |
273 | 116 |
signature=c(celda.mod="celdaList"), |
274 | 117 |
function(celda.mod){ celda.mod@run.params }) |
275 |
-#@export |
|
276 |
-# setGeneric("runParams<-", |
|
277 |
-# function(celda.mod, value){ standardGeneric("runParams<-") }) |
|
278 |
-# setReplaceMethod("runParams", "celdaModel", |
|
279 |
-# function(celda.mod, value){ |
|
280 |
-# celda.mod@run.params = value |
|
281 |
-# celda.mod |
|
282 |
-# }) |
|
118 |
+ |
|
283 | 119 |
|
284 | 120 |
#' @title Get final celda models from a celdaList |
285 | 121 |
#' @description Returns all models generated during a `celdaGridSearch()` run. |
... | ... |
@@ -292,38 +128,19 @@ setGeneric("resList", |
292 | 128 |
setMethod("resList", |
293 | 129 |
signature=c(celda.mod="celdaList"), |
294 | 130 |
function(celda.mod){ celda.mod@res.list }) |
295 |
-#@export |
|
296 |
-#setGeneric("resList<-", |
|
297 |
-# function(celda.mod, value){ standardGeneric("resList<-") }) |
|
298 |
-# setReplaceMethod("resList", "celdaModel", |
|
299 |
-# function(celda.mod, value){ |
|
300 |
-# celda.mod@resList = value |
|
301 |
-# celda.mod |
|
302 |
-# }) |
|
303 |
- |
|
304 |
-setMethod("countChecksum", |
|
305 |
- signature=c(celda.mod="celdaList"), |
|
306 |
- function(celda.mod){ celda.mod@count.checksum }) |
|
307 | 131 |
|
308 | 132 |
|
309 | 133 |
#' @title Get perplexity for every model in a celdaList |
310 | 134 |
#' @description Returns perplexity for each model in a celdaList as calculated by `perplexity().` |
311 | 135 |
#' @return List. Contains one celdaModel object for each of the parameters specified in the `runParams()` of the provided celda list. |
312 | 136 |
#' @examples |
313 |
-#' celda.CG.grid.model.perplexities = getPerplexity(celda.CG.grid.search.res) |
|
137 |
+#' celda.CG.grid.model.perplexities = celdaPerplexity(celda.CG.grid.search.res) |
|
314 | 138 |
#' @export |
315 |
-setGeneric("getPerplexity", |
|
316 |
- function(celda.mod){ standardGeneric("getPerplexity") }) |
|
317 |
-setMethod("getPerplexity", |
|
139 |
+setGeneric("celdaPerplexity", |
|
140 |
+ function(celda.mod){ standardGeneric("celdaPerplexity") }) |
|
141 |
+setMethod("celdaPerplexity", |
|
318 | 142 |
signature=c(celda.mod="celdaList"), |
319 | 143 |
function(celda.mod){ celda.mod@perplexity }) |
320 |
-# setGeneric("setPerplexity<-", |
|
321 |
-# function(celda.mod, value){ standardGeneric("setPerplexity<-") }) |
|
322 |
-# setReplaceMethod("setPerplexity", "celdaModel", |
|
323 |
-# function(celda.mod, value){ |
|
324 |
-# celda.mod@perplexity = value |
|
325 |
-# celda.mod |
|
326 |
-# }) |
|
327 | 144 |
|
328 | 145 |
|
329 | 146 |
################################################################################ |
... | ... |
@@ -154,12 +154,12 @@ celda_C = function(counts, sample.label=NULL, K, alpha=1, beta=1, |
154 | 154 |
logMessages(date(), ".. Finished chain", i, "with seed", current.seed, logfile=logfile, append=TRUE, verbose=verbose) |
155 | 155 |
} |
156 | 156 |
best.result = methods::new("celda_C", |
157 |
- clustering=list(z=best.result$z, K=best.result$K), |
|
158 |
- modelPriors=list(alpha=best.result$alpha, beta=best.result$beta), |
|
157 |
+ clusters=list(z=best.result$z), |
|
158 |
+ params=list(K=best.result$K, alpha=best.result$alpha, beta=best.result$beta, |
|
159 |
+ sample.label=best.result$sample.label, |
|
160 |
+ count.checksum=best.result$count.checksum), |
|
159 | 161 |
completeLogLik=best.result$completeLogLik, |
160 | 162 |
finalLogLik=best.result$finalLogLik, seed=best.result$seed, |
161 |
- sample.label=best.result$sample.label, |
|
162 |
- count.checksum=best.result$count.checksum, |
|
163 | 163 |
names=best.result$names) |
164 | 164 |
best.result = reorder.celda_C(counts = counts, res = best.result) |
165 | 165 |
|
... | ... |
@@ -306,14 +306,16 @@ simulateCells.celda_C = function(model, S=5, C.Range=c(50, 100), N.Range=c(500,1 |
306 | 306 |
cell.counts = processCounts(cell.counts) |
307 | 307 |
names = list(row=rownames(cell.counts), column=colnames(cell.counts), |
308 | 308 |
sample=unique(cell.sample.label)) |
309 |
- result = methods::new("celda_C", clustering=list(z=z, K=K), |
|
310 |
- modelPriors=list(alpha=alpha, beta=beta), seed=seed, |
|
311 |
- sample.label=cell.sample.label, names=names, |
|
312 |
- count.checksum=digest::digest(cell.counts, algo="md5")) |
|
309 |
+ result = methods::new("celda_C", clusters=list(z=z), |
|
310 |
+ params=list(alpha=alpha, beta=beta, seed=seed, |
|
311 |
+ count.checksum=digest::digest(cell.counts, algo="md5"), |
|
312 |
+ K=K), |
|
313 |
+ sample.label=cell.sample.label, |
|
314 |
+ names=names) |
|
313 | 315 |
class(result) = "celda_C" |
314 | 316 |
result = reorder.celda_C(counts = cell.counts, res = result) |
315 | 317 |
|
316 |
- return(list(z=result@clustering$z, counts=processCounts(cell.counts), |
|
318 |
+ return(list(z=result@clusters$z, counts=processCounts(cell.counts), |
|
317 | 319 |
sample.label=cell.sample.label, K=K, alpha=alpha, |
318 | 320 |
beta=beta, C.Range=C.Range, N.Range=N.Range, S=S)) |
319 | 321 |
} |
... | ... |
@@ -337,8 +339,8 @@ setMethod("factorizeMatrix", |
337 | 339 |
counts = processCounts(counts) |
338 | 340 |
compareCountMatrix(counts, celda.mod) |
339 | 341 |
|
340 |
- K = celda.mod@clustering$K |
|
341 |
- z = celda.mod@clustering$z |
|
342 |
+ K = celda.mod@params$K |
|
343 |
+ z = celda.mod@clusters$z |
|
342 | 344 |
alpha = celda.mod@modelPriors$alpha |
343 | 345 |
beta = celda.mod@modelPriors$beta |
344 | 346 |
sample.label = celda.mod@sample.label |
... | ... |
@@ -487,11 +489,11 @@ cC.reDecomposeCounts = function(counts, s, z, previous.z, n.G.by.CP, K) { |
487 | 489 |
setMethod("clusterProbability", |
488 | 490 |
signature(celda.mod = "celda_C"), |
489 | 491 |
function(counts, celda.mod, log=FALSE, ...) { |
490 |
- z = celda.mod@clustering$z |
|
492 |
+ z = celda.mod@clusters$z |
|
491 | 493 |
sample.label = celda.mod@sample.label |
492 | 494 |
s = as.integer(sample.label) |
493 | 495 |
|
494 |
- K = celda.mod@clustering$K |
|
496 |
+ K = celda.mod@params$K |
|
495 | 497 |
alpha = celda.mod@modelPriors$alpha |
496 | 498 |
beta = celda.mod@modelPriors$beta |
497 | 499 |
|
... | ... |
@@ -558,10 +560,10 @@ setMethod("perplexity", |
558 | 560 |
|
559 | 561 |
|
560 | 562 |
reorder.celda_C = function(counts, res){ |
561 |
- if(res@clustering$K > 2 & isTRUE(length(unique(res@clustering$z)) > 1)) { |
|
562 |
- res@clustering$z = as.integer(as.factor(res@clustering$z)) |
|
563 |
+ if(res@params$K > 2 & isTRUE(length(unique(res@clusters$z)) > 1)) { |
|
564 |
+ res@clusters$z = as.integer(as.factor(res@clusters$z)) |
|
563 | 565 |
fm <- factorizeMatrix(counts = counts, celda.mod = res) |
564 |
- unique.z = sort(unique(res@clustering$z)) |
|
566 |
+ unique.z = sort(unique(res@clusters$z)) |
|
565 | 567 |
d <- cosineDist(fm$posterior$module[,unique.z]) |
566 | 568 |
h <- stats::hclust(d, method = "complete") |
567 | 569 |
res <- recodeClusterZ(res, from = h$order, to = 1:length(h$order)) |
... | ... |
@@ -586,7 +588,7 @@ setMethod("celdaHeatmap", |
586 | 588 |
signature(celda.mod = "celda_C"), |
587 | 589 |
function(counts, celda.mod, feature.ix, ...) { |
588 | 590 |
norm = normalizeCounts(counts, normalize="proportion", transformation.fun=sqrt) |
589 |
- plotHeatmap(norm[feature.ix,], z=celda.mod@clustering$z, ...) |
|
591 |
+ plotHeatmap(norm[feature.ix,], z=celda.mod@clusters$z, ...) |
|
590 | 592 |
}) |
591 | 593 |
|
592 | 594 |
|
... | ... |
@@ -617,9 +619,9 @@ setMethod("celdaTsne", |
617 | 619 |
compareCountMatrix(counts, celda.mod) |
618 | 620 |
|
619 | 621 |
## Checking if max.cells and min.cluster.size will work |
620 |
- if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@clustering$K)) { |
|
622 |
+ if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@params$K)) { |
|
621 | 623 |
stop(paste0("Cannot distribute ", max.cells, " cells among ", |
622 |
- celda.mod@clustering$K, " clusters while maintaining a minumum of ", |
|
624 |
+ celda.mod@params$K, " clusters while maintaining a minumum of ", |
|
623 | 625 |
min.cluster.size, |
624 | 626 |
" cells per cluster. Try increasing 'max.cells' or decreasing 'min.cluster.size'.")) |
625 | 627 |
} |
... | ... |
@@ -628,7 +630,7 @@ setMethod("celdaTsne", |
628 | 630 |
total.cells.to.remove = ncol(counts) - max.cells |
629 | 631 |
z.include = rep(TRUE, ncol(counts)) |
630 | 632 |
if(total.cells.to.remove > 0) { |
631 |
- z.ta = tabulate(celda.mod@clustering$z, celda.mod@clustering$K) |
|
633 |
+ z.ta = tabulate(celda.mod@clusters$z, celda.mod@params$K) |
|
632 | 634 |
|
633 | 635 |
## Number of cells that can be sampled from each cluster without |
634 | 636 |
## going below the minimum threshold |
... | ... |
@@ -644,7 +646,7 @@ setMethod("celdaTsne", |
644 | 646 |
|
645 | 647 |
## Perform sampling for each cluster |
646 | 648 |
for(i in which(cluster.n.to.sample > 0)) { |
647 |
- z.include[sample(which(celda.mod@clustering$z == i), cluster.n.to.sample[i])] = FALSE |
|
649 |
+ z.include[sample(which(celda.mod@clusters$z == i), cluster.n.to.sample[i])] = FALSE |
|
648 | 650 |
} |
649 | 651 |
} |
650 | 652 |
cell.ix = which(z.include) |
... | ... |
@@ -681,7 +683,7 @@ setMethod("celdaProbabilityMap", |
681 | 683 |
counts = processCounts(counts) |
682 | 684 |
compareCountMatrix(counts, celda.mod) |
683 | 685 |
|
684 |
- z.include = which(tabulate(celda.mod@clustering$z, celda.mod@clustering$K) > 0) |
|
686 |
+ z.include = which(tabulate(celda.mod@clusters$z, celda.mod@params$K) > 0) |
|
685 | 687 |
|
686 | 688 |
level = match.arg(level) |
687 | 689 |
factorized <- factorizeMatrix(celda.mod = celda.mod, |
... | ... |
@@ -215,12 +215,15 @@ celda_CG = function(counts, sample.label=NULL, K, L, |
215 | 215 |
|
216 | 216 |
## Peform reordering on final Z and Y assigments: |
217 | 217 |
best.result = methods::new("celda_CG", |
218 |
- clustering=list(z=z.best, y=y.best, K=K, L=L), |
|
219 |
- modelPriors=list(alpha=alpha, beta=beta, delta=delta, gamma=gamma), |
|
220 |
- completeLogLik=ll, finalLogLik=ll.best, |
|
221 |
- seed=current.seed, |
|
222 |
- sample.label=sample.label, names=names, |
|
223 |
- count.checksum=count.checksum) |
|
218 |
+ clusters=list(z=z.best, y=y.best), |
|
219 |
+ params=list(K=K, L=L, alpha=alpha, beta=beta, |
|
220 |
+ delta=delta, gamma=gamma, |
|
221 |
+ seed=current.seed, |
|
222 |
+ count.checksum=count.checksum), |
|
223 |
+ completeLogLik=ll, |
|
224 |
+ finalLogLik=ll.best, |
|
225 |
+ sample.label=sample.label, |
|
226 |
+ names=names) |
|
224 | 227 |
best.result = reorder.celda_CG(counts = counts, res = best.result) |
225 | 228 |
|
226 | 229 |
end.time = Sys.time() |
... | ... |
@@ -325,14 +328,15 @@ simulateCells.celda_CG = function(model, S=5, C.Range=c(50,100), N.Range=c(500,1 |
325 | 328 |
names = list(row=rownames(cell.counts), column=colnames(cell.counts), |
326 | 329 |
sample=unique(cell.sample.label)) |
327 | 330 |
result = methods::new("celda_CG", |
328 |
- clustering=list(z=z, y=y, K=K, L=L), |
|
329 |
- modelPriors=list(alpha=alpha, beta=beta, delta=delta, gamma=gamma), |
|
330 |
- seed =seed, sample.label=cell.sample.label, names=names, |
|
331 |
- count.checksum=digest::digest(cell.counts, algo="md5")) |
|
331 |
+ clusters=list(z=z, y=y), |
|
332 |
+ params=list(K=K, L=L, alpha=alpha, beta=beta, delta=delta, |
|
333 |
+ gamma=gamma, seed=seed, |
|
334 |
+ count.checksum=digest::digest(cell.counts, algo="md5")), |
|
335 |
+ sample.label=cell.sample.label, names=names) |
|
332 | 336 |
|
333 | 337 |
result = reorder.celda_CG(counts = cell.counts, res = result) |
334 | 338 |
|
335 |
- return(list(z=result@clustering$z, y=result@clustering$y, sample.label=cell.sample.label, |
|
339 |
+ return(list(z=result@clusters$z, y=result@clusters$y, sample.label=cell.sample.label, |
|
336 | 340 |
counts=cell.counts, K=K, L=L, C.Range=C.Range, |
337 | 341 |
N.Range=N.Range, S=S, alpha=alpha, beta=beta, gamma=gamma, |
338 | 342 |
delta=delta, seed=seed)) |
... | ... |
@@ -357,10 +361,10 @@ setMethod("factorizeMatrix", |
357 | 361 |
counts = processCounts(counts) |
358 | 362 |
compareCountMatrix(counts, celda.mod) |
359 | 363 |
|
360 |
- K = celda.mod@clustering$K |
|
361 |
- L = celda.mod@clustering$L |
|
362 |
- z = celda.mod@clustering$z |
|
363 |
- y = celda.mod@clustering$y |
|
364 |
+ K = celda.mod@params$K |
|
365 |
+ L = celda.mod@params$L |
|
366 |
+ z = celda.mod@clusters$z |
|
367 |
+ y = celda.mod@clusters$y |
|
364 | 368 |
alpha = celda.mod@modelPriors$alpha |
365 | 369 |
beta = celda.mod@modelPriors$beta |
366 | 370 |
delta = celda.mod@modelPriors$delta |
... | ... |
@@ -566,10 +570,10 @@ setMethod("clusterProbability", |
566 | 570 |
function(counts, celda.mod, log=FALSE, ...) { |
567 | 571 |
|
568 | 572 |
s = as.integer(celda.mod@sample.label) |
569 |
- z = celda.mod@clustering$z |
|
570 |
- K = celda.mod@clustering$K |
|
571 |
- y = celda.mod@clustering$y |
|
572 |
- L = celda.mod@clustering$L |
|
573 |
+ z = celda.mod@clusters$z |
|
574 |
+ K = celda.mod@params$K |
|
575 |
+ y = celda.mod@clusters$y |
|
576 |
+ L = celda.mod@params$L |
|
573 | 577 |
alpha = celda.mod@modelPriors$alpha |
574 | 578 |
delta = celda.mod@modelPriors$delta |
575 | 579 |
beta = celda.mod@modelPriors$beta |
... | ... |
@@ -651,10 +655,10 @@ setMethod("perplexity", |
651 | 655 |
|
652 | 656 |
reorder.celda_CG = function(counts, res){ |
653 | 657 |
# Reorder K |
654 |
- if(res@clustering$K > 2 & isTRUE(length(unique(res@clustering$z)) > 1)) { |
|
655 |
- res@clustering$z = as.integer(as.factor(res@clustering$z)) |
|
658 |
+ if(res@params$K > 2 & isTRUE(length(unique(res@clusters$z)) > 1)) { |
|
659 |
+ res@clusters$z = as.integer(as.factor(res@clusters$z)) |
|
656 | 660 |
fm <- factorizeMatrix(counts = counts, celda.mod = res, type="posterior") |
657 |
- unique.z = sort(unique(res@clustering$z)) |
|
661 |
+ unique.z = sort(unique(res@clusters$z)) |
|
658 | 662 |
d <- cosineDist(fm$posterior$cell.population[,unique.z]) |
659 | 663 |
h <- stats::hclust(d, method = "complete") |
660 | 664 |
|
... | ... |
@@ -662,10 +666,10 @@ reorder.celda_CG = function(counts, res){ |
662 | 666 |
} |
663 | 667 |
|
664 | 668 |
# Reorder L |
665 |
- if(res@clustering$L > 2 & isTRUE(length(unique(res@clustering$y)) > 1)) { |
|
666 |
- res@clustering$y = as.integer(as.factor(res@clustering$y)) |
|
669 |
+ if(res@params$L > 2 & isTRUE(length(unique(res@clusters$y)) > 1)) { |
|
670 |
+ res@clusters$y = as.integer(as.factor(res@clusters$y)) |
|
667 | 671 |
fm <- factorizeMatrix(counts = counts, celda.mod = res, type="posterior") |
668 |
- unique.y = sort(unique(res@clustering$y)) |
|
672 |
+ unique.y = sort(unique(res@clusters$y)) |
|
669 | 673 |
cs <- prop.table(t(fm$posterior$cell.population[unique.y,]), 2) |
670 | 674 |
d <- cosineDist(cs) |
671 | 675 |
h <- stats::hclust(d, method = "complete") |
... | ... |
@@ -695,7 +699,7 @@ setMethod("celdaHeatmap", |
695 | 699 |
top = celda::topRank(fm$proportions$module, n=nfeatures) |
696 | 700 |
ix = unlist(top$index) |
697 | 701 |
norm = normalizeCounts(counts, normalize="proportion", transformation.fun=sqrt) |
698 |
- plotHeatmap(norm[ix,], z=celda.mod@clustering$z, y=celda.mod@clustering$y[ix], ...) |
|
702 |
+ plotHeatmap(norm[ix,], z=celda.mod@clusters$z, y=celda.mod@clusters$y[ix], ...) |
|
699 | 703 |
}) |
700 | 704 |
|
701 | 705 |
|
... | ... |
@@ -723,9 +727,9 @@ setMethod("celdaTsne", |
723 | 727 |
seed=12345, ...) { |
724 | 728 |
|
725 | 729 |
## Checking if max.cells and min.cluster.size will work |
726 |
- if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@clustering$K)) { |
|
730 |
+ if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@params$K)) { |
|
727 | 731 |
stop(paste0("Cannot distribute ", max.cells, " cells among ", |
728 |
- celda.mod@clustering$K, " clusters while maintaining a minumum of ", |
|
732 |
+ celda.mod@params$K, " clusters while maintaining a minumum of ", |
|
729 | 733 |
min.cluster.size, " cells per cluster. Try increasing 'max.cells' or decreasing 'min.cluster.size'.")) |
730 | 734 |
} |
731 | 735 |
|
... | ... |
@@ -745,7 +749,7 @@ setMethod("celdaTsne", |
745 | 749 |
total.cells.to.remove = ncol(counts) - max.cells |
746 | 750 |
z.include = rep(TRUE, ncol(counts)) |
747 | 751 |
if(total.cells.to.remove > 0) { |
748 |
- z.ta = tabulate(celda.mod@clustering$z, celda.mod@clustering$K) |
|
752 |
+ z.ta = tabulate(celda.mod@clusters$z, celda.mod@params$K) |
|
749 | 753 |
|
750 | 754 |
## Number of cells that can be sampled from each cluster without |
751 | 755 |
## going below the minimum threshold |
... | ... |
@@ -761,7 +765,7 @@ setMethod("celdaTsne", |
761 | 765 |
|
762 | 766 |
## Perform sampling for each cluster |
763 | 767 |
for(i in which(cluster.n.to.sample > 0)) { |
764 |
- z.include[sample(which(celda.mod@clustering$z == i), cluster.n.to.sample[i])] = FALSE |
|
768 |
+ z.include[sample(which(celda.mod@clusters$z == i), cluster.n.to.sample[i])] = FALSE |
|
765 | 769 |
} |
766 | 770 |
} |
767 | 771 |
cell.ix = which(z.include) |
... | ... |
@@ -799,8 +803,8 @@ setMethod("celdaProbabilityMap", |
799 | 803 |
|
800 | 804 |
level = match.arg(level) |
801 | 805 |
factorized <- factorizeMatrix(celda.mod = celda.mod, counts = counts) |
802 |
- z.include = which(tabulate(celda.mod@clustering$z, celda.mod@clustering$K) > 0) |
|
803 |
- y.include = which(tabulate(celda.mod@clustering$y, celda.mod@clustering$L) > 0) |
|
806 |
+ z.include = which(tabulate(celda.mod@clusters$z, celda.mod@params$K) > 0) |
|
807 |
+ y.include = which(tabulate(celda.mod@clusters$y, celda.mod@params$L) > 0) |
|
804 | 808 |
|
805 | 809 |
if(level == "cell.population") { |
806 | 810 |
pop <- factorized$proportions$cell.population[y.include,z.include,drop=FALSE] |
... | ... |
@@ -859,7 +863,7 @@ setMethod("featureModuleLookup", |
859 | 863 |
} |
860 | 864 |
for(x in 1:length(feature)){ |
861 | 865 |
if(feature[x] %in% rownames(counts)){ |
862 |
- list[x] <- celda.mod@clustering$y[which(rownames(counts) == feature[x])] |
|
866 |
+ list[x] <- celda.mod@clusters$y[which(rownames(counts) == feature[x])] |
|
863 | 867 |
}else{ |
864 | 868 |
list[x] <- paste0("No feature was identified matching '", feature[x], "'.") |
865 | 869 |
} |
... | ... |
@@ -148,10 +148,10 @@ celda_G = function(counts, L, beta=1, delta=1, gamma=1, |
148 | 148 |
|
149 | 149 |
|
150 | 150 |
best.result = methods::new("celda_G", |
151 |
- clustering=list(y=y.best, L=L), |
|
152 |
- modelPriors=list(beta=beta, delta=delta, gamma=gamma), |
|
151 |
+ clusters=list(y=y.best), |
|
152 |
+ params=list(L=L, beta=beta, delta=delta, gamma=gamma, |
|
153 |
+ count.checksum=count.checksum, seed=current.seed), |
|
153 | 154 |
completeLogLik=ll, finalLogLik=ll.best, |
154 |
- count.checksum=count.checksum, seed=current.seed, |
|
155 | 155 |
names=names) |
156 | 156 |
best.result = reorder.celda_G(counts = counts, res = best.result) |
157 | 157 |
|
... | ... |
@@ -310,13 +310,14 @@ simulateCells.celda_G = function(model, C=100, N.Range=c(500,1000), G=100, |
310 | 310 |
## Peform reordering on final Z and Y assigments: |
311 | 311 |
cell.counts = processCounts(cell.counts) |
312 | 312 |
names = list(row=rownames(cell.counts), column=colnames(cell.counts)) |
313 |
- result = methods::new("celda_G", clustering=list(y=y, L=L), |
|
314 |
- modelPriors=list(beta=beta, delta=delta, gamma=gamma), |
|
315 |
- seed=seed, names=names, |
|
316 |
- count.checksum=digest::digest(cell.counts, algo="md5")) |
|
313 |
+ result = methods::new("celda_G", clusters=list(y=y), |
|
314 |
+ params=list(L=L, beta=beta, delta=delta, gamma=gamma, |
|
315 |
+ seed=seed, |
|
316 |
+ count.checksum=digest::digest(cell.counts, algo="md5")), |
|
317 |
+ names=names) |
|
317 | 318 |
result = reorder.celda_G(counts = cell.counts, res = result) |
318 | 319 |
|
319 |
- return(list(y=result@clustering$y, counts=processCounts(cell.counts), L=L, |
|
320 |
+ return(list(y=result@clusters$y, counts=processCounts(cell.counts), L=L, |
|
320 | 321 |
beta=beta, delta=delta, gamma=gamma, seed=seed)) |
321 | 322 |
} |
322 | 323 |
|
... | ... |
@@ -339,8 +340,8 @@ setMethod("factorizeMatrix", |
339 | 340 |
counts = processCounts(counts) |
340 | 341 |
compareCountMatrix(counts, celda.mod) |
341 | 342 |
|
342 |
- L = celda.mod@clustering$L |
|
343 |
- y = celda.mod@clustering$y |
|
343 |
+ L = celda.mod@params$L |
|
344 |
+ y = celda.mod@clusters$y |
|
344 | 345 |
beta = celda.mod@modelPriors$beta |
345 | 346 |
delta = celda.mod@modelPriors$delta |
346 | 347 |
gamma = celda.mod@modelPriors$gamma |
... | ... |
@@ -508,8 +509,8 @@ cG.reDecomposeCounts = function(counts, y, previous.y, n.TS.by.C, n.by.G, L) { |
508 | 509 |
setMethod("clusterProbability", |
509 | 510 |
signature(celda.mod = "celda_G"), |
510 | 511 |
function(counts, celda.mod, log=FALSE, ...) { |
511 |
- y = celda.mod@clustering$y |
|
512 |
- L = celda.mod@clustering$L |
|
512 |
+ y = celda.mod@clusters$y |
|
513 |
+ L = celda.mod@params$L |
|
513 | 514 |
delta = celda.mod@modelPriors$delta |
514 | 515 |
beta = celda.mod@modelPriors$beta |
515 | 516 |
gamma = celda.mod@modelPriors$gamma |
... | ... |
@@ -574,10 +575,10 @@ setMethod("perplexity", |
574 | 575 |
|
575 | 576 |
|
576 | 577 |
reorder.celda_G = function(counts, res) { |
577 |
- if(res@clustering$L > 2 & isTRUE(length(unique(res@clustering$y)) > 1)) { |
|
578 |
- res@clustering$y = as.integer(as.factor(res@clustering$y)) |
|
578 |
+ if(res@params$L > 2 & isTRUE(length(unique(res@clusters$y)) > 1)) { |
|
579 |
+ res@clusters$y = as.integer(as.factor(res@clusters$y)) |
|
579 | 580 |
fm <- factorizeMatrix(counts = counts, celda.mod = res) |
580 |
- unique.y = sort(unique(res@clustering$y)) |
|
581 |
+ unique.y = sort(unique(res@clusters$y)) |
|
581 | 582 |
cs = prop.table(t(fm$posterior$cell[unique.y,]), 2) |
582 | 583 |
d <- cosineDist(cs) |
583 | 584 |
h <- stats::hclust(d, method = "complete") |
... | ... |
@@ -606,7 +607,7 @@ setMethod("celdaHeatmap", |
606 | 607 |
top = topRank(fm$proportions$module, n=nfeatures) |
607 | 608 |
ix = unlist(top$index) |
608 | 609 |
norm = normalizeCounts(counts, normalize="proportion", transformation.fun=sqrt) |
609 |
- plotHeatmap(norm[ix,], y=celda.mod@clustering$y[ix], ...) |
|
610 |
+ plotHeatmap(norm[ix,], y=celda.mod@clusters$y[ix], ...) |
|
610 | 611 |
}) |
611 | 612 |
|
612 | 613 |
#' @title tSNE for celda_G |
... | ... |
@@ -687,7 +688,7 @@ setMethod("featureModuleLookup", |
687 | 688 |
} |
688 | 689 |
for(x in 1:length(feature)){ |
689 | 690 |
if(feature[x] %in% rownames(counts)){ |
690 |
- list[x] <- celda.mod@clustering$y[which(rownames(counts) == feature[x])] |
|
691 |
+ list[x] <- celda.mod@clusters$y[which(rownames(counts) == feature[x])] |
|
691 | 692 |
}else{ |
692 | 693 |
list[x] <- paste0("No feature was identified matching '", |
693 | 694 |
feature[x], "'.") |
... | ... |
@@ -103,10 +103,10 @@ recodeClusterZ = function(celda.mod, from, to) { |
103 | 103 |
if (length(setdiff(from, to)) != 0) { |
104 | 104 |
stop("All values in 'from' must have a mapping in 'to'") |
105 | 105 |
} |
106 |
- if (is.null(celda.mod@clustering$z)) { |
|
106 |
+ if (is.null(celda.mod@clusters$z)) { |
|
107 | 107 |
stop("Provided celda.mod argument does not have a z attribute") |
108 | 108 |
} |
109 |
- celda.mod@clustering$z = plyr::mapvalues(celda.mod@clustering$z, from, to) |
|
109 |
+ celda.mod@clusters$z = plyr::mapvalues(celda.mod@clusters$z, from, to) |
|
110 | 110 |
return(celda.mod) |
111 | 111 |
} |
112 | 112 |
|
... | ... |
@@ -125,10 +125,10 @@ recodeClusterY = function(celda.mod, from, to) { |
125 | 125 |
if (length(setdiff(from, to)) != 0) { |
126 | 126 |
stop("All values in 'from' must have a mapping in 'to'") |
127 | 127 |
} |
128 |
- if (is.null(celda.mod@clustering$y)) { |
|
128 |
+ if (is.null(celda.mod@clusters$y)) { |
|
129 | 129 |
stop("Provided celda.mod argument does not have a y attribute") |
130 | 130 |
} |
131 |
- celda.mod@clustering$y = plyr::mapvalues(celda.mod@clustering$y, from, to) |
|
131 |
+ celda.mod@clusters$y = plyr::mapvalues(celda.mod@clusters$y, from, to) |
|
132 | 132 |
return(celda.mod) |
133 | 133 |
} |
134 | 134 |
|
... | ... |
@@ -146,13 +146,13 @@ recodeClusterY = function(celda.mod, from, to) { |
146 | 146 |
#' @export |
147 | 147 |
compareCountMatrix = function(counts, celda.mod, error.on.mismatch=TRUE) { |
148 | 148 |
if (methods::.hasSlot(celda.mod, "y")) { |
149 |
- if (nrow(counts) != length(celda.mod@clustering$y)) { |
|
149 |
+ if (nrow(counts) != length(celda.mod@clusters$y)) { |
|
150 | 150 |
stop(paste0("The provided celda object was generated from a counts matrix with a different number of features than the one provided.")) |
151 | 151 |
} |
152 | 152 |
} |
153 | 153 |
|
154 | 154 |
if (methods::.hasSlot(celda.mod, "z")) { |
155 |
- if (ncol(counts) != length(celda.mod@clustering$z)) { |
|
155 |
+ if (ncol(counts) != length(celda.mod@clusters$z)) { |
|
156 | 156 |
stop(paste0("The provided celda object was generated from a counts matrix with a different number of cells than the one provided.")) |
157 | 157 |
} |
158 | 158 |
} |
... | ... |
@@ -27,21 +27,21 @@ differentialExpression <- function(counts, celda.mod, c1, c2 = NULL, only.pos = |
27 | 27 |
compareCountMatrix(counts, celda.mod) |
28 | 28 |
|
29 | 29 |
if (is.null(c2)){ |
30 |
- c2 <- sort(setdiff(unique(celda.mod@clustering$z),c1)) |
|
30 |
+ c2 <- sort(setdiff(unique(celda.mod@clusters$z),c1)) |
|
31 | 31 |
} |
32 | 32 |
if (length(c1) > 1){ |
33 | 33 |
cells1 <- |
34 |
- celda.mod@names$column[which(celda.mod@clustering$z %in% c1)] |
|
34 |
+ celda.mod@names$column[which(celda.mod@clusters$z %in% c1)] |
|
35 | 35 |
}else{ |
36 | 36 |
cells1 <- |
37 |
- celda.mod@names$column[which(celda.mod@clustering$z == c1)] |
|
37 |
+ celda.mod@names$column[which(celda.mod@clusters$z == c1)] |
|
38 | 38 |
} |
39 | 39 |
if (length(c2) > 1){ |
40 | 40 |
cells2 <- |
41 |
- celda.mod@names$column[which(celda.mod@clustering$z %in% c2)] |
|
41 |
+ celda.mod@names$column[which(celda.mod@clusters$z %in% c2)] |
|
42 | 42 |
}else{ |
43 | 43 |
cells2 <- |
44 |
- celda.mod@names$column[which(celda.mod@clustering$z == c2)] |
|
44 |
+ celda.mod@names$column[which(celda.mod@clusters$z == c2)] |
|
45 | 45 |
} |
46 | 46 |
mat <- counts[,c(cells1,cells2)] |
47 | 47 |
log_normalized_mat <- normalizeCounts(mat, normalize="cpm", transformation.fun=log1p) |
... | ... |
@@ -64,7 +64,7 @@ recursive.splitZ = function(counts, s, K, alpha, beta, min.cell = 3, seed=12345) |
64 | 64 |
if(isTRUE(cluster.split.flag[i])) { |
65 | 65 |
ix = which(overall.z == i) |
66 | 66 |
res = suppressMessages(.celda_C(counts[,ix], K=2, stop.iter = 1, split.on.iter=-1, split.on.last=FALSE, nchains=1, seed=seed, verbose=FALSE, initialize="random")) |
67 |
- cluster.splits[cbind(ix, i)] = res@clustering$z |
|
67 |
+ cluster.splits[cbind(ix, i)] = res@clusters$z |
|
68 | 68 |
cluster.split.flag[i] = FALSE |
69 | 69 |
} |
70 | 70 |
} |
... | ... |
@@ -109,7 +109,7 @@ recursive.splitY = function(counts, L, beta, delta, gamma, z=NULL, K=NULL, K.sub |
109 | 109 |
temp.z[ix] = (current.top.z + 1):(current.top.z + z.ta[i]) |
110 | 110 |
} else { |
111 | 111 |
clustLabel = suppressMessages(.celda_C(counts[,z == i], K=K.subclusters, max.iter=5, stop.iter=1, algorithm="EM", nchains=1, split.on.iter=-1, split.on.last=FALSE, verbose=FALSE, initialize="random")) |
112 |
- temp.z[ix] = clustLabel@clustering$z + current.top.z |
|
112 |
+ temp.z[ix] = clustLabel@clusters$z + current.top.z |
|
113 | 113 |
} |
114 | 114 |
current.top.z = max(temp.z, na.rm=TRUE) |
115 | 115 |
} |
... | ... |
@@ -117,7 +117,7 @@ recursive.splitY = function(counts, L, beta, delta, gamma, z=NULL, K=NULL, K.sub |
117 | 117 |
} else { |
118 | 118 |
if(ncol(counts) > max.cells) { |
119 | 119 |
res = .celda_C(counts, K=max.cells, stop.iter = 1, split.on.iter=-1, split.on.last=FALSE, nchains=3, seed=seed, verbose=FALSE) |
120 |
- temp.z = res@clustering$z |
|
120 |
+ temp.z = res@clusters$z |
|
121 | 121 |
} else { |
122 | 122 |
temp.z = 1:ncol(counts) |
123 | 123 |
} |
... | ... |
@@ -142,7 +142,7 @@ recursive.splitY = function(counts, L, beta, delta, gamma, z=NULL, K=NULL, K.sub |
142 | 142 |
if(isTRUE(cluster.split.flag[i])) { |
143 | 143 |
ix = which(overall.y == i) |
144 | 144 |
res = suppressMessages(.celda_G(counts[ix,], L=2, max.iter = 5, split.on.iter=-1, split.on.last=FALSE, nchains=1, seed=seed, verbose=FALSE, initialize="random")) |
145 |
- cluster.splits[cbind(ix, i)] = res@clustering$y |
|
145 |
+ cluster.splits[cbind(ix, i)] = res@clusters$y |
|
146 | 146 |
cluster.split.flag[i] = FALSE |
147 | 147 |
} |
148 | 148 |
} |
... | ... |
@@ -15,7 +15,7 @@ cC.splitZ = function(counts, m.CP.by.S, n.G.by.CP, n.CP, s, z, K, nS, nG, alpha, |
15 | 15 |
clust.split = vector("list", K) |
16 | 16 |
for(i in z.to.split) { |
17 | 17 |
clustLabel = suppressMessages(.celda_C(counts[,z == i], K=2, max.iter=5, split.on.iter=-1, split.on.last=FALSE)) |
18 |
- clust.split[[i]] = clustLabel@clustering$z |
|
18 |
+ clust.split[[i]] = clustLabel@clusters$z |
|
19 | 19 |
} |
20 | 20 |
|
21 | 21 |
## Find second best assignment give current assignments for each cell |
... | ... |
@@ -107,7 +107,7 @@ cCG.splitZ = function(counts, m.CP.by.S, n.TS.by.C, n.TS.by.CP, n.by.G, n.by.TS, |
107 | 107 |
clust.split = vector("list", K) |
108 | 108 |
for(i in z.to.split) { |
109 | 109 |
clustLabel = suppressMessages(.celda_C(counts[,z == i], K=2, max.iter=5, split.on.iter=-1, split.on.last=FALSE)) |
110 |
- clust.split[[i]] = clustLabel@clustering$z |
|
110 |
+ clust.split[[i]] = clustLabel@clusters$z |
|
111 | 111 |
} |
112 | 112 |
|
113 | 113 |
## Find second best assignment give current assignments for each cell |
... | ... |
@@ -200,7 +200,7 @@ cCG.splitY = function(counts, y, m.CP.by.S, n.G.by.CP, n.TS.by.C, n.TS.by.CP, n. |
200 | 200 |
temp.z[ix] = (current.top.z + 1):(current.top.z + z.ta[i]) |
201 | 201 |
} else { |
202 | 202 |
clustLabel = suppressMessages(.celda_C(counts[,z == i], K=K.subclusters, max.iter=5, split.on.iter=-1, split.on.last=FALSE)) |
203 |
- temp.z[ix] = clustLabel@clustering$z + current.top.z |
|
203 |
+ temp.z[ix] = clustLabel@clusters$z + current.top.z |
|
204 | 204 |
} |
205 | 205 |
current.top.z = max(temp.z, na.rm=TRUE) |
206 | 206 |
} |
... | ... |
@@ -226,7 +226,7 @@ cCG.splitY = function(counts, y, m.CP.by.S, n.G.by.CP, n.TS.by.C, n.TS.by.CP, n. |
226 | 226 |
clust.split = vector("list", L) |
227 | 227 |
for(i in y.to.split) { |
228 | 228 |
clustLabel = suppressMessages(.celda_G(temp.n.G.by.CP[y == i,], L=2, max.iter=5, split.on.iter=-1, split.on.last=FALSE)) |
229 |
- clust.split[[i]] = clustLabel@clustering$y |
|
229 |
+ clust.split[[i]] = clustLabel@clusters$y |
|
230 | 230 |
} |
231 | 231 |
|
232 | 232 |
## Find second best assignment give current assignments for each cell |
... | ... |
@@ -323,7 +323,7 @@ cG.splitY = function(counts, y, n.TS.by.C, n.by.TS, n.by.G, nG.by.TS, nM, nG, L, |
323 | 323 |
clust.split = vector("list", L) |
324 | 324 |
for(i in y.to.split) { |
325 | 325 |
clustLabel = suppressMessages(.celda_G(counts[y == i,], L=2, max.iter=5, split.on.iter=-1, split.on.last=FALSE)) |
326 |
- clust.split[[i]] = clustLabel@clustering$y |
|
326 |
+ clust.split[[i]] = clustLabel@clusters$y |
|
327 | 327 |
} |
328 | 328 |
|
329 | 329 |
## Find second best assignment give current assignments for each cell |
330 | 330 |
similarity index 72% |
331 | 331 |
rename from man/getPerplexity.Rd |
332 | 332 |
rename to man/celdaPerplexity.Rd |
... | ... |
@@ -1,10 +1,10 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/all_generics.R |
3 |
-\name{getPerplexity} |
|
4 |
-\alias{getPerplexity} |
|
3 |
+\name{celdaPerplexity} |
|
4 |
+\alias{celdaPerplexity} |
|
5 | 5 |
\title{Get perplexity for every model in a celdaList} |
6 | 6 |
\usage{ |
7 |
-getPerplexity(celda.mod) |
|
7 |
+celdaPerplexity(celda.mod) |
|
8 | 8 |
} |
9 | 9 |
\value{ |
10 | 10 |
List. Contains one celdaModel object for each of the parameters specified in the `runParams()` of the provided celda list. |
... | ... |
@@ -13,5 +13,5 @@ List. Contains one celdaModel object for each of the parameters specified in the |
13 | 13 |
Returns perplexity for each model in a celdaList as calculated by `perplexity().` |
14 | 14 |
} |
15 | 15 |
\examples{ |
16 |
-celda.CG.grid.model.perplexities = getPerplexity(celda.CG.grid.search.res) |
|
16 |
+celda.CG.grid.model.perplexities = celdaPerplexity(celda.CG.grid.search.res) |
|
17 | 17 |
} |
18 | 18 |
deleted file mode 100644 |
... | ... |
@@ -1,17 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{clustering} |
|
4 |
-\alias{clustering} |
|
5 |
-\title{Get clustering parameters and outcomes from a celda model.} |
|
6 |
-\usage{ |
|
7 |
-clustering(celda.mod) |
|
8 |
-} |
|
9 |
-\value{ |
|
10 |
-List. Contains K, z (for celda_C and celda_CG models), and/or L, y (for celda_G and celda_CG models.) |
|
11 |
-} |
|
12 |
-\description{ |
|
13 |
-Returns the K/L parameters provided for modeling, as well as the corresponding z/y results. |
|
14 |
-} |
|
15 |
-\examples{ |
|
16 |
-clustering(celda.CG.mod) |
|
17 |
-} |
18 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,17 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/all_generics.R |
|
3 |
+\name{clusters} |
|
4 |
+\alias{clusters} |
|
5 |
+\title{Get clustering outcomes from a celda model} |
|
6 |
+\usage{ |
|
7 |
+clusters(celda.mod) |
|
8 |
+} |
|
9 |
+\value{ |
|
10 |
+List. Contains z (for celda_C and celda_CG models) and/or y (for celda_G and celda_CG models) |
|
11 |
+} |
|
12 |
+\description{ |
|
13 |
+Returns the z / y results corresponding to the cell / gene cluster labels determined by the provided celda model. |
|
14 |
+} |
|
15 |
+\examples{ |
|
16 |
+clusters(celda.CG.mod) |
|
17 |
+} |
0 | 18 |
deleted file mode 100644 |
... | ... |
@@ -1,17 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{countChecksum} |
|
4 |
-\alias{countChecksum} |
|
5 |
-\title{Get count matrix checksum for comparison} |
|
6 |
-\usage{ |
|
7 |
-countChecksum(celda.mod) |
|
8 |
-} |
|
9 |
-\value{ |
|
10 |
-Character. The MD5 hash of the count matrix used to generate the provided celda model. |
|
11 |
-} |
|
12 |
-\description{ |
|
13 |
-Retrieves the MD5 checksum of the count matrix used to generate the provided celda mdoel. |
|
14 |
-} |
|
15 |
-\examples{ |
|
16 |
-countChecksum(celda.CG.mod) |
|
17 |
-} |
18 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,17 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{finalLogLik} |
|
4 |
-\alias{finalLogLik} |
|
5 |
-\title{Get final log-likelihood} |
|
6 |
-\usage{ |
|
7 |
-finalLogLik(celda.mod) |
|
8 |
-} |
|
9 |
-\value{ |
|
10 |
-Numeric. The log-likelihood at the final step of Gibbs sampling used to generate the model. |
|
11 |
-} |
|
12 |
-\description{ |
|
13 |
-Retrieves the final log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
|
14 |
-} |
|
15 |
-\examples{ |
|
16 |
-finalLogLik(celda.CG.mod) |
|
17 |
-} |
18 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,17 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{initialSeed} |
|
4 |
-\alias{initialSeed} |
|
5 |
-\title{Get seed used to generate model} |
|
6 |
-\usage{ |
|
7 |
-initialSeed(celda.mod) |
|
8 |
-} |
|
9 |
-\value{ |
|
10 |
-Numeric. The random seed used to generate the provided celda model. |
|
11 |
-} |
|
12 |
-\description{ |
|
13 |
-Retrieves the random seed used to generate a celda model. |
|
14 |
-} |
|
15 |
-\examples{ |
|
16 |
-initialSeed(celda.CG.mod) |
|
17 |
-} |
18 | 0 |
similarity index 75% |
19 | 1 |
rename from man/completeLogLik.Rd |
20 | 2 |
rename to man/logLikelihoodHistory.Rd |
... | ... |
@@ -1,10 +1,10 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/all_generics.R |
3 |
-\name{completeLogLik} |
|
4 |
-\alias{completeLogLik} |
|
3 |
+\name{logLikelihoodHistory} |
|
4 |
+\alias{logLikelihoodHistory} |
|
5 | 5 |
\title{Get log-likelihood history} |
6 | 6 |
\usage{ |
7 |
-completeLogLik(celda.mod) |
|
7 |
+logLikelihoodHistory(celda.mod) |
|
8 | 8 |
} |
9 | 9 |
\value{ |
10 | 10 |
Numeric. The log-likelihood at each step of Gibbs sampling used to generate the model. |
... | ... |
@@ -13,5 +13,5 @@ Numeric. The log-likelihood at each step of Gibbs sampling used to generate the |
13 | 13 |
Retrieves the complete log-likelihood from all iterations of Gibbs sampling used to generate a celda model. |
14 | 14 |
} |
15 | 15 |
\examples{ |
16 |
-completeLogLik(celda.CG.mod) |
|
16 |
+logLikelihoodHistory(celda.CG.mod) |
|
17 | 17 |
} |
18 | 18 |
deleted file mode 100644 |
... | ... |
@@ -1,17 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/all_generics.R |
|
3 |
-\name{modelPriors} |
|
4 |
-\alias{modelPriors} |
|
5 |
-\title{Get model prior parameters from a celda model.} |
|
6 |
-\usage{ |
|
7 |
-modelPriors(celda.mod) |
|
8 |
-} |
|
9 |
-\value{ |
|
10 |
-List. Contains alpha, beta (for celda_C and celda_CG models), or delta, gamma (for celda_G and celda_CG models). |
|
11 |
-} |
|
12 |
-\description{ |
|
13 |
-Returns the model priors (e.g. alpha, beta) provided at model creation for a given celda model. |
|
14 |
-} |
|
15 |
-\examples{ |
|
16 |
-modelPriors(celda.CG.mod) |
|
17 |
-} |
18 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,17 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/all_generics.R |
|
3 |
+\name{params} |
|
4 |
+\alias{params} |
|
5 |
+\title{Get parameter values provided for celda model creation} |
|
6 |
+\usage{ |
|
7 |
+params(celda.mod) |
|
8 |
+} |
|
9 |
+\value{ |
|
10 |
+List. Contains the model-specific parameters for the provided celda model object depending on its class. |
|
11 |
+} |
|
12 |
+\description{ |
|
13 |
+Retrieves the K/L, model priors (e.g. alpha, beta), random seed, and count matrix checksum parameters provided during the creation of the provided celda model. |
|
14 |
+} |
|
15 |
+\examples{ |
|
16 |
+params(celda.CG.mod) |
|
17 |
+} |
... | ... |
@@ -12,7 +12,7 @@ factorized = factorizeMatrix(counts=celdaC.sim$counts, celda.mod = model_C) |
12 | 12 |
test_that(desc = "Testing simulation and celda_C model", { |
13 | 13 |
expect_equal(typeof(celdaC.sim$counts), "integer") |
14 | 14 |
expect_true(all(sweep(factorized$counts$sample, 2, colSums(factorized$counts$sample), "/") == factorized$proportions$sample)) |
15 |
- expect_true(ncol(factorized$proportions$module) == model_C@clustering$K) |
|
15 |
+ expect_true(ncol(factorized$proportions$module) == model_C@params$K) |
|
16 | 16 |
expect_true(all(is.numeric(completeLogLik(celda.mod = model_C)))) |
17 | 17 |
expect_equal(max(completeLogLik(celda.mod = model_C)), finalLogLik(model_C)) |
18 | 18 |
|
... | ... |
@@ -131,7 +131,7 @@ test_that(desc = "Testing recodeClusterZ with celda_C", { |
131 | 131 |
expect_error(recodeClusterZ(celda.mod = model_C, from = c(1,2,3,4,5), to = c(1,2,3,4,6))) |
132 | 132 |
expect_error(recodeClusterZ(celda.mod = model_C, from = c(1,2,3,4,6), to = c(1,2,3,4,5))) |
133 | 133 |
new.recoded <- recodeClusterZ(celda.mod = model_C, from = c(1,2,3,4,5), to = c(5,4,3,2,1)) |
134 |
- expect_equal(model_C@clustering$z == 1, new.recoded@clustering$z == 5) |
|
134 |
+ expect_equal(model_C@clusters$z == 1, new.recoded@clusters$z == 5) |
|
135 | 135 |
}) |
136 | 136 |
|
137 | 137 |
# compareCountMatrix |
... | ... |
@@ -159,9 +159,9 @@ test_that(desc = "Checking topRank to see if it runs without errors", { |
159 | 159 |
|
160 | 160 |
# plotHeatmap |
161 | 161 |
test_that(desc = "Testing plotHeatmap with celda_C", { |
162 |
- expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@clustering$K), "Length of z must match number of columns in counts matrix") |
|
163 |
- expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@clustering$z, scale.row = model_C), "'scale.row' needs to be of class 'function'") |
|
164 |
- expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@clustering$z, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
162 |
+ expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@params$K), "Length of z must match number of columns in counts matrix") |
|
163 |
+ expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@clusters$z, scale.row = model_C), "'scale.row' needs to be of class 'function'") |
|
164 |
+ expect_error(plotHeatmap(counts = celdaC.sim$counts, z = model_C@clusters$z, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
165 | 165 |
}) |
166 | 166 |
|
167 | 167 |
|
... | ... |
@@ -170,15 +170,15 @@ test_that(desc = "Testing plotHeatmap with celda_C, including annotations",{ |
170 | 170 |
annot <- as.data.frame(c(rep(x = 1, times = ncol(celdaC.sim$counts) - 100),rep(x = 2, 100))) |
171 | 171 |
|
172 | 172 |
rownames(annot) <- colnames(celdaC.sim$counts) |
173 |
- expect_equal(names(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.cell = annot, z = model_C@clustering$z)), |
|
173 |
+ expect_equal(names(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.cell = annot, z = model_C@clusters$z)), |
|
174 | 174 |
c("tree_row", "tree_col", "gtable")) |
175 | 175 |
|
176 | 176 |
rownames(annot) <- NULL |
177 |
- expect_equal(names(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.feature = as.matrix(annot), z = model_C@clustering$z)), |
|
177 |
+ expect_equal(names(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.feature = as.matrix(annot), z = model_C@clusters$z)), |
|
178 | 178 |
c("tree_row", "tree_col", "gtable")) |
179 | 179 |
|
180 | 180 |
rownames(annot) <- rev(colnames(celdaC.sim$counts)) |
181 |
- expect_error(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.cell = annot, z = model_C@clustering$z), |
|
181 |
+ expect_error(plotHeatmap(celda.mod = model_C, counts = celdaC.sim$counts, annotation.cell = annot, z = model_C@clusters$z), |
|
182 | 182 |
"Row names of 'annotation.cell' are different than the column names of 'counts'") |
183 | 183 |
}) |
184 | 184 |
|
... | ... |
@@ -214,22 +214,22 @@ test_that(desc = "Testing differentialExpression with celda_C", { |
214 | 214 |
test_that(desc = "Testing celdaTsne with celda_C when model class is changed, should error",{ |
215 | 215 |
model_X <- model_C |
216 | 216 |
class(model_X) <- "celda_X" |
217 |
- expect_error(celdaTsne(counts=celdaC.sim$counts, celda.mod=model_X, max.cells=length(model_C@clustering$z), min.cluster.size=10), |
|
217 |
+ expect_error(celdaTsne(counts=celdaC.sim$counts, celda.mod=model_X, max.cells=length(model_C@clusters$z), min.cluster.size=10), |
|
218 | 218 |
"unable to find an inherited method for function 'celdaTsne' for signature '\"celda_X\"'") |
219 | 219 |
}) |
220 | 220 |
|
221 | 221 |
test_that(desc = "Testing celdaTsne with celda_C including all cells",{ |
222 |
- tsne = celdaTsne(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=length(model_C@clustering$z), min.cluster.size=10) |
|
223 |
- plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_C@clustering$z) |
|
224 |
- expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_C@clustering$z)) |
|
222 |
+ tsne = celdaTsne(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=length(model_C@clusters$z), min.cluster.size=10) |
|
223 |
+ plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_C@clusters$z) |
|
224 |
+ expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_C@clusters$z)) |
|
225 | 225 |
expect_true(!is.null(plot.obj)) |
226 | 226 |
}) |
227 | 227 |
|
228 | 228 |
test_that(desc = "Testing celdaTsne with celda_C including a subset of cells",{ |
229 | 229 |
expect_success(expect_error(tsne <- celdaTsne(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=50, min.cluster.size=50))) |
230 | 230 |
tsne <- celdaTsne(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=100, min.cluster.size=10) |
231 |
- plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_C@clustering$z) |
|
232 |
- expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_C@clustering$z) && sum(!is.na(tsne[,1])) == 100) |
|
231 |
+ plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_C@clusters$z) |
|
232 |
+ expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_C@clusters$z) && sum(!is.na(tsne[,1])) == 100) |
|
233 | 233 |
expect_true(!is.null(plot.obj)) |
234 | 234 |
}) |
235 | 235 |
|
... | ... |
@@ -175,7 +175,7 @@ test_that(desc = "Testing recodeClusterY with celda_CG", { |
175 | 175 |
expect_error(recodeClusterY(celda.mod = model_CG, from = c(1,2,3,4,5), to = c(1,2,4,3,6))) |
176 | 176 |
expect_error(recodeClusterY(celda.mod = model_CG, from = c(1,2,3,4,6), to = c(1,2,4,3,5))) |
177 | 177 |
new.recoded <- recodeClusterY(celda.mod = model_CG, from = c(1,2,3,4,5), to = c(3,2,1,4,5)) |
178 |
- expect_equal(model_CG@clustering$y == 1, new.recoded@clustering$y == 3) |
|
178 |
+ expect_equal(model_CG@clusters$y == 1, new.recoded@clusters$y == 3) |
|
179 | 179 |
}) |
180 | 180 |
|
181 | 181 |
# recodeClusterZ |
... | ... |
@@ -184,7 +184,7 @@ test_that(desc = "Testing recodeClusterZ with celda_CG", { |
184 | 184 |
expect_error(recodeClusterZ(celda.mod = model_CG, from = c(1,2,3,4,5), to = c(1,2,3,4,6))) |
185 | 185 |
expect_error(recodeClusterZ(celda.mod = model_CG, from = c(1,2,3,4,6), to = c(1,2,3,4,5))) |
186 | 186 |
new.recoded <- recodeClusterZ(celda.mod = model_CG, from = c(1,2,3,4,5), to = c(5,4,3,2,1)) |
187 |
- expect_equal(model_CG@clustering$z == 1, new.recoded@clustering$z == 5) |
|
187 |
+ expect_equal(model_CG@clusters$z == 1, new.recoded@clusters$z == 5) |
|
188 | 188 |
}) |
189 | 189 |
|
190 | 190 |
# compareCountMatrix |
... | ... |
@@ -214,15 +214,15 @@ test_that(desc = "Testing topRank with celda_CG", { |
214 | 214 |
|
215 | 215 |
# plotHeatmap |
216 | 216 |
test_that(desc = "Testing plotHeatmap with celda_CG", { |
217 |
- expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$y, y = model_CG@clustering$y), "Length of z must match number of columns in counts matrix") |
|
218 |
- expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$z), "Length of y must match number of rows in counts matrix") |
|
219 |
- expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$y, scale.row = model_CG), "'scale.row' needs to be of class 'function'") |
|
220 |
- expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$y, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
221 |
- expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$y, cell.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
222 |
- expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = NULL, y = model_CG@clustering$y, cell.ix = 1:10, color.scheme = "sequential")), c("tree_row", "tree_col", "gtable")) |
|
223 |
- expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$y, feature.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
224 |
- expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = NULL, feature.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
225 |
- expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clustering$z, y = model_CG@clustering$y, cell.ix = 1:10, color.scheme = "sequential", annotation.color = "default")), c("tree_row", "tree_col", "gtable")) |
|
217 |
+ expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$y, y = model_CG@clusters$y), "Length of z must match number of columns in counts matrix") |
|
218 |
+ expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$z), "Length of y must match number of rows in counts matrix") |
|
219 |
+ expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$y, scale.row = model_CG), "'scale.row' needs to be of class 'function'") |
|
220 |
+ expect_error(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$y, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
221 |
+ expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$y, cell.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
222 |
+ expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = NULL, y = model_CG@clusters$y, cell.ix = 1:10, color.scheme = "sequential")), c("tree_row", "tree_col", "gtable")) |
|
223 |
+ expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$y, feature.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
224 |
+ expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = NULL, feature.ix = 1:10)), c("tree_row", "tree_col", "gtable")) |
|
225 |
+ expect_equal(names(plotHeatmap(counts = celdaCG.sim$counts, z = model_CG@clusters$z, y = model_CG@clusters$y, cell.ix = 1:10, color.scheme = "sequential", annotation.color = "default")), c("tree_row", "tree_col", "gtable")) |
|
226 | 226 |
}) |
227 | 227 |
|
228 | 228 |
#plotHeatmap with annotations |
... | ... |
@@ -234,12 +234,12 @@ test_that(desc = "Testing plotHeatmap with annotations", { |
234 | 234 |
colnames(annot.cell) <- "cell" |
235 | 235 |
rownames(annot.feature) <- rownames(celdaCG.sim$counts) |
236 | 236 |
colnames(annot.feature) <- "feature" |
237 |
- expect_equal(names(plotHeatmap(celda.mod = model_CG, counts = celdaCG.sim$counts, annotation.cell = annot.cell, annotation.feature = annot.feature, z = model_CG@clustering$z, y = model_CG@clustering$y)), |
|
237 |
+ expect_equal(names(plotHeatmap(celda.mod = model_CG, counts = celdaCG.sim$counts, annotation.cell = annot.cell, annotation.feature = annot.feature, z = model_CG@clusters$z, y = model_CG@clusters$y)), |
|
238 | 238 |
c("tree_row", "tree_col", "gtable")) |
239 | 239 |
|
240 | 240 |
rownames(annot.cell) <- NULL |
241 | 241 |
rownames(annot.feature) <- NULL |
242 |
- expect_equal(names(plotHeatmap(celda.mod = model_CG, counts = celdaCG.sim$counts, annotation.cell = as.matrix(annot.cell), annotation.feature = as.matrix(annot.feature), z = model_CG@clustering$z, y = model_CG@clustering$y)), |
|
242 |
+ expect_equal(names(plotHeatmap(celda.mod = model_CG, counts = celdaCG.sim$counts, annotation.cell = as.matrix(annot.cell), annotation.feature = as.matrix(annot.feature), z = model_CG@clusters$z, y = model_CG@clusters$y)), |
|
243 | 243 |
c("tree_row", "tree_col", "gtable")) |
244 | 244 |
|
245 | 245 |
}) |
... | ... |
@@ -289,7 +289,7 @@ test_that(desc = "Testing differentialExpression for celda_CG", { |
289 | 289 |
# plotDimReduce |
290 | 290 |
test_that(desc = "Testing plotDimReduce* with celda_CG", { |
291 | 291 |
celda.tsne <- celdaTsne(counts = celdaCG.sim$counts, max.iter = 50, celda.mod = model_CG, max.cells = 500) |
292 |
- expect_equal(names(plotDimReduceCluster(dim1 = celda.tsne[,1], dim2 = celda.tsne[,2],cluster = as.factor(model_CG@clustering$z),specific_clusters = c(1,2,3))), |
|
292 |
+ expect_equal(names(plotDimReduceCluster(dim1 = celda.tsne[,1], dim2 = celda.tsne[,2],cluster = as.factor(model_CG@clusters$z),specific_clusters = c(1,2,3))), |
|
293 | 293 |
c("data", "layers", "scales", "mapping", "theme", "coordinates", "facet", "plot_env", "labels", "guides")) |
294 | 294 |
expect_equal(names(plotDimReduceModule(dim1 = celda.tsne[,1], dim2 = celda.tsne[,2], counts = celdaCG.sim$counts, celda.mod = model_CG, modules = c("L1", "L2"))), |
295 | 295 |
c("data", "layers", "scales", "mapping", "theme", "coordinates", "facet", "plot_env", "labels")) |
... | ... |
@@ -322,9 +322,9 @@ test_that(desc = "Testing celdaTsne with celda_CG when model class is changed, s |
322 | 322 |
}) |
323 | 323 |
|
324 | 324 |
test_that(desc = "Testing celdaTsne.celda_CG with all cells",{ |
325 |
- tsne = celdaTsne(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=length(model_CG@clustering$z)) |
|
326 |
- plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_CG@clustering$z) |
|
327 |
- expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_CG@clustering$z)) |
|
325 |
+ tsne = celdaTsne(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=length(model_CG@clusters$z)) |
|
326 |
+ plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_CG@clusters$z) |
|
327 |
+ expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_CG@clusters$z)) |
|
328 | 328 |
expect_true(!is.null(plot.obj)) |
329 | 329 |
|
330 | 330 |
tsne = celdaTsne(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=ncol(celdaCG.sim$counts), modules=1:2) |
... | ... |
@@ -334,15 +334,15 @@ test_that(desc = "Testing celdaTsne.celda_CG with all cells",{ |
334 | 334 |
test_that(desc = "Testing celdaTsne.celda_CG with subset of cells",{ |
335 | 335 |
expect_success(expect_error(tsne <- celdaTsne(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=50, min.cluster.size=50))) |
336 | 336 |
tsne = celdaTsne(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=100, min.cluster.size=10) |
337 |
- plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_CG@clustering$z) |
|
338 |
- expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_CG@clustering$z) && sum(!is.na(tsne[,1])) == 100) |
|
337 |
+ plot.obj = plotDimReduceCluster(tsne[,1], tsne[,2], model_CG@clusters$z) |
|
338 |
+ expect_true(ncol(tsne) == 2 & nrow(tsne) == length(model_CG@clusters$z) && sum(!is.na(tsne[,1])) == 100) |
|
339 | 339 |
expect_true(!is.null(plot.obj)) |
340 | 340 |
}) |
341 | 341 |
|
342 | 342 |
# featureModuleLookup |
343 | 343 |
test_that(desc = "Testing featureModuleLookup with celda_CG", { |
344 | 344 |
res = featureModuleLookup(celdaCG.sim$counts, model_CG, "Gene_1") |
345 |
- expect_true(res == model_CG@clustering$y[1]) |
|
345 |
+ expect_true(res == model_CG@clusters$y[1]) |
|
346 | 346 |
|
347 | 347 |
res = featureModuleLookup(celdaCG.sim$counts, model_CG, "Gene_2", exact.match = FALSE) |
348 | 348 |
expect_true(length(res) == 11) |
... | ... |
@@ -129,7 +129,7 @@ test_that(desc = "Testing recodeClusterY with celda_G", { |
129 | 129 |
expect_error(recodeClusterY(celda.mod = model_G, from = c(1,2,3,4,5), to = c(1,2,3,4,6))) |
130 | 130 |
expect_error(recodeClusterY(celda.mod = model_G, from = c(1,2,3,4,6), to = c(1,2,3,4,5))) |
131 | 131 |
new.recoded = recodeClusterY(celda.mod = model_G, from = c(1,2,3,4,5), to = c(5,4,3,2,1)) |
132 |
- expect_equal(model_G@clustering$y == 1, new.recoded@clustering$y == 5) |
|
132 |
+ expect_equal(model_G@clusters$y == 1, new.recoded@clusters$y == 5) |
|
133 | 133 |
}) |
134 | 134 |
|
135 | 135 |
# compareCountMatrix |
... | ... |
@@ -156,9 +156,9 @@ test_that(desc = "Testing topRank function with celda_G", { |
156 | 156 |
|
157 | 157 |
# plotHeatmap |
158 | 158 |
test_that(desc = "Testing plotHeatmap with celda_G", { |
159 |
- expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@clustering$L), "Length of y must match number of rows in counts matrix") |
|
160 |
- expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@clustering$y, scale.row = "scale"), "'scale.row' needs to be of class 'function'") |
|
161 |
- expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@clustering$y, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
159 |
+ expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@params$L), "Length of y must match number of rows in counts matrix") |
|
160 |
+ expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@clusters$y, scale.row = "scale"), "'scale.row' needs to be of class 'function'") |
|
161 |
+ expect_error(plotHeatmap(counts = celdaG.sim$counts, y = model_G@clusters$y, trim = 3), "'trim' should be a 2 element vector specifying the lower and upper boundaries") |
|
162 | 162 |
}) |
163 | 163 |
|
164 | 164 |
test_that(desc = "Testing plotHeatmap with celda_G, including annotations",{ |
... | ... |
@@ -166,15 +166,15 @@ test_that(desc = "Testing plotHeatmap with celda_G, including annotations",{ |
166 | 166 |
rownames(annot) <- rownames(celdaG.sim$counts) |
167 | 167 |
colnames(annot) <- "label" |
168 | 168 |
|
169 |
- expect_equal(names(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = annot, y = model_G@clustering$y)), |
|
169 |
+ expect_equal(names(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = annot, y = model_G@clusters$y)), |
|
170 | 170 |
c("tree_row", "tree_col", "gtable")) |
171 | 171 |
|
172 | 172 |
rownames(annot) <- NULL |
173 |
- expect_equal(names(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = as.matrix(annot), y = model_G@clustering$y)), |
|
173 |
+ expect_equal(names(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = as.matrix(annot), y = model_G@clusters$y)), |
|
174 | 174 |
c("tree_row", "tree_col", "gtable")) |
175 | 175 |
|
176 | 176 |
rownames(annot) <- rev(rownames(celdaG.sim$counts)) |
177 |
- expect_error(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = annot, y = model_G@clustering$y), |
|
177 |
+ expect_error(plotHeatmap(celda.mod = model_G, counts = celdaG.sim$counts, annotation.feature = annot, y = model_G@clusters$y), |
|
178 | 178 |
"Row names of 'annotation.feature' are different than the row names of 'counts'") |
179 | 179 |
}) |
180 | 180 |
|
... | ... |
@@ -234,7 +234,7 @@ test_that(desc = "Testing celdaTsne with celda_G including a subset of cells",{ |
234 | 234 |
# featureModuleLookup |
235 | 235 |
test_that(desc = "Testing featureModuleLookup with celda_G", { |
236 | 236 |
res = featureModuleLookup(celdaG.sim$counts, model_G, "Gene_1") |
237 |
- expect_true(res == model_G@clustering$y[1]) |
|
237 |
+ expect_true(res == model_G@clusters$y[1]) |
|
238 | 238 |
res = featureModuleLookup(celdaG.sim$counts, model_G, "Gene_2", exact.match = FALSE) |
239 | 239 |
expect_true(length(res) == 11) |
240 | 240 |
res = featureModuleLookup(celdaG.sim$counts, model_G, "XXXXXXX") |