... | ... |
@@ -61,22 +61,22 @@ simulateObservedMatrix = function(C=300, G=100, K=3, N.Range=c(500,1000), beta = |
61 | 61 |
|
62 | 62 |
# This function calculates the log-likelihood |
63 | 63 |
# |
64 |
-# omat Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells |
|
64 |
+# counts Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells |
|
65 | 65 |
# z Integer vector. Cell population labels |
66 | 66 |
# phi Numeric matrix. Rows represent features and columns represent cell populations |
67 | 67 |
# eta Numeric matrix. Rows represent features and columns represent cell populations |
68 | 68 |
# theta Numeric vector. Proportion of truely expressed transcripts |
69 |
-decon.calcLL = function(omat, z, phi, eta, theta){ |
|
70 |
- #ll = sum( t(omat) * log( (1-conP )*geneDist[z,] + conP * conDist[z, ] + 1e-20 ) ) # when dist_mat are K x G matrices |
|
71 |
- ll = sum( t(omat) * log( theta * t(phi)[z,] + (1-theta) * t(eta)[z,] + 1e-20 )) |
|
69 |
+decon.calcLL = function(counts, z, phi, eta, theta){ |
|
70 |
+ #ll = sum( t(counts) * log( (1-conP )*geneDist[z,] + conP * conDist[z, ] + 1e-20 ) ) # when dist_mat are K x G matrices |
|
71 |
+ ll = sum( t(counts) * log( theta * t(phi)[z,] + (1-theta) * t(eta)[z,] + 1e-20 )) |
|
72 | 72 |
return(ll) |
73 | 73 |
} |
74 | 74 |
|
75 | 75 |
# This function calculates the log-likelihood of background distribution decontamination |
76 | 76 |
# |
77 | 77 |
# bgDist Numeric matrix. Rows represent feature and columns are the times that the background-distribution has been replicated. |
78 |
-bg.calcLL = function(omat, cellDist, bgDist, theta){ |
|
79 |
- ll = sum( t(omat) * log( theta * t(cellDist) + (1-theta) * t(bgDist) + 1e-20) ) |
|
78 |
+bg.calcLL = function(counts, cellDist, bgDist, theta){ |
|
79 |
+ ll = sum( t(counts) * log( theta * t(cellDist) + (1-theta) * t(bgDist) + 1e-20) ) |
|
80 | 80 |
return(ll) |
81 | 81 |
} |
82 | 82 |
|
... | ... |
@@ -86,7 +86,7 @@ bg.calcLL = function(omat, cellDist, bgDist, theta){ |
86 | 86 |
# phi Numeric matrix. Rows represent features and columns represent cell populations |
87 | 87 |
# eta Numeric matrix. Rows represent features and columns represent cell populations |
88 | 88 |
# theta Numeric vector. Proportion of truely expressed transctripts |
89 |
-cD.calcEMDecontamination = function(omat, phi, eta, theta, z, K, beta, delta ) { |
|
89 |
+cD.calcEMDecontamination = function(counts, phi, eta, theta, z, K, beta, delta ) { |
|
90 | 90 |
|
91 | 91 |
# Notes: use fix-point iteration to update prior for theta, no need to feed delta anymore |
92 | 92 |
log.Pr = log( t(phi)[z,] + 1e-20) + log(theta + 1e-20 ) |
... | ... |
@@ -96,12 +96,12 @@ cD.calcEMDecontamination = function(omat, phi, eta, theta, z, K, beta, delta ) |
96 | 96 |
Pc = 1 - Pr |
97 | 97 |
delta.v2 = MCMCprecision::fit_dirichlet( matrix( c( Pr, Pc) , ncol = 2 ) )$alpha |
98 | 98 |
|
99 |
- est.rmat = t(Pr) * omat |
|
99 |
+ est.rmat = t(Pr) * counts |
|
100 | 100 |
rn.G.by.K = colSumByGroup.numeric(est.rmat, z, K) |
101 | 101 |
cn.G.by.K = rowSums(rn.G.by.K) - rn.G.by.K |
102 | 102 |
|
103 | 103 |
#update parameters |
104 |
- theta = (colSums(est.rmat) + delta.v2[1]) / (colSums(omat) + sum(delta.v2) ) |
|
104 |
+ theta = (colSums(est.rmat) + delta.v2[1]) / (colSums(counts) + sum(delta.v2) ) |
|
105 | 105 |
phi = normalizeCounts(rn.G.by.K, normalize="proportion", pseudocount.normalize =beta ) |
106 | 106 |
eta = normalizeCounts(cn.G.by.K, normalize="proportion", pseudocount.normalize = beta) |
107 | 107 |
|
... | ... |
@@ -111,18 +111,18 @@ cD.calcEMDecontamination = function(omat, phi, eta, theta, z, K, beta, delta ) |
111 | 111 |
|
112 | 112 |
# This function updates decontamination using background distribution |
113 | 113 |
# |
114 |
-cD.calcEMbgDecontamination = function(omat, cellDist, bgDist, theta, beta, delta){ |
|
114 |
+cD.calcEMbgDecontamination = function(counts, cellDist, bgDist, theta, beta, delta){ |
|
115 | 115 |
|
116 |
- meanN.by.C = apply(omat, 2, mean) |
|
117 |
- log.Pr = log( t(cellDist) + 1e-20) + log( theta + 1e-20) # + log( t(omat) / meanN.by.C ) # better when without panelty |
|
116 |
+ meanN.by.C = apply(counts, 2, mean) |
|
117 |
+ log.Pr = log( t(cellDist) + 1e-20) + log( theta + 1e-20) # + log( t(counts) / meanN.by.C ) # better when without panelty |
|
118 | 118 |
log.Pc = log( t(bgDist) + 1e-20) + log( 1-theta + 2e-20) |
119 | 119 |
|
120 | 120 |
Pr = exp( log.Pr) / (exp(log.Pr) + exp( log.Pc) ) |
121 | 121 |
|
122 |
- est.rmat = t(Pr) * omat |
|
122 |
+ est.rmat = t(Pr) * counts |
|
123 | 123 |
|
124 | 124 |
# Update paramters |
125 |
- theta = (colSums(est.rmat) + delta) / (colSums(omat) + 2*delta) |
|
125 |
+ theta = (colSums(est.rmat) + delta) / (colSums(counts) + 2*delta) |
|
126 | 126 |
cellDist = normalizeCounts(est.rmat, normalize="proportion", pseudocount.normalize =beta) |
127 | 127 |
|
128 | 128 |
return( list("est.rmat"=est.rmat, "theta"=theta, "cellDist"=cellDist) ) |
... | ... |
@@ -130,7 +130,7 @@ cD.calcEMbgDecontamination = function(omat, cellDist, bgDist, theta, beta, delta |
130 | 130 |
|
131 | 131 |
|
132 | 132 |
#' This function updates decontamination on dataset with multiple batches |
133 |
-#' @param omat Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells. |
|
133 |
+#' @param counts Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells. |
|
134 | 134 |
#' @param z Integer vector. Cell population labels. Default NULL |
135 | 135 |
#' @param batch Integer vector. Cell batch labels. Default NULL |
136 | 136 |
#' @param max.iter Integer. Maximum iterations of EM algorithm. Default to be 200 |
... | ... |
@@ -140,26 +140,26 @@ cD.calcEMbgDecontamination = function(omat, cellDist, bgDist, theta, beta, delta |
140 | 140 |
#' @param verbose Logical. Whether to print log messages. Default TRUE |
141 | 141 |
#' @param seed Integer. Passed to set.seed(). Default to be 1234567. If NULL, no calls to `set.seed()` are made. |
142 | 142 |
#' @examples |
143 |
-#' decon.c = DecontX( omat = contamination.sim$rmat + contamination.sim$cmat, z=contamination.sim$z, max.iter=3) |
|
144 |
-#' decon.bg = DecontX( omat=contamination.sim$rmat + contamination.sim$cmat, max.iter=3 ) |
|
143 |
+#' decon.c = DecontX( counts = contamination.sim$rmat + contamination.sim$cmat, z=contamination.sim$z, max.iter=3) |
|
144 |
+#' decon.bg = DecontX( counts=contamination.sim$rmat + contamination.sim$cmat, max.iter=3 ) |
|
145 | 145 |
#' @export |
146 |
-DecontX = function( omat , z=NULL, batch=NULL, max.iter=200, beta=1e-6, delta=10, logfile=NULL, verbose=TRUE, seed=1234567 ) { |
|
146 |
+DecontX = function( counts , z=NULL, batch=NULL, max.iter=200, beta=1e-6, delta=10, logfile=NULL, verbose=TRUE, seed=1234567 ) { |
|
147 | 147 |
|
148 | 148 |
|
149 | 149 |
if ( !is.null(batch) ) { |
150 | 150 |
|
151 | 151 |
# Set result lists upfront for all cells from different batches |
152 | 152 |
logLikelihood = c() |
153 |
- est.rmat = matrix(NA, ncol = ncol(omat) , nrow = nrow(omat ) , dimnames = list( rownames( omat) , colnames( omat ) ) ) |
|
154 |
- theta = rep(NA, ncol(omat ) ) |
|
155 |
- est.conp = rep(NA, ncol(omat) ) |
|
153 |
+ est.rmat = matrix(NA, ncol = ncol(counts) , nrow = nrow(counts ) , dimnames = list( rownames( counts) , colnames( counts ) ) ) |
|
154 |
+ theta = rep(NA, ncol(counts ) ) |
|
155 |
+ est.conp = rep(NA, ncol(counts) ) |
|
156 | 156 |
|
157 | 157 |
batch.index = unique(batch) |
158 | 158 |
|
159 | 159 |
for ( BATCH in batch.index ) { |
160 |
- omat.BATCH = omat[, batch == BATCH ] |
|
160 |
+ counts.BATCH = counts[, batch == BATCH ] |
|
161 | 161 |
if( !is.null(z) ) { z.BATCH = z[ batch == BATCH ] } else { z.BATCH = z } |
162 |
- res.BATCH = DecontXoneBatch( omat = omat.BATCH, z = z.BATCH, batch = BATCH ,max.iter = max.iter, beta = beta, delta = delta, logfile=logfile, verbose=verbose, seed=seed ) |
|
162 |
+ res.BATCH = DecontXoneBatch( counts = counts.BATCH, z = z.BATCH, batch = BATCH ,max.iter = max.iter, beta = beta, delta = delta, logfile=logfile, verbose=verbose, seed=seed ) |
|
163 | 163 |
|
164 | 164 |
est.rmat[, batch == BATCH ] = res.BATCH$res.list$est.rmat |
165 | 165 |
est.conp[ batch == BATCH ] = res.BATCH$res.list$est.conp |
... | ... |
@@ -179,7 +179,7 @@ DecontX = function( omat , z=NULL, batch=NULL, max.iter=200, beta=1e-6, delta=1 |
179 | 179 |
return( list("run.params"=run.params, "res.list"=res.list, "method"=method ) ) |
180 | 180 |
} |
181 | 181 |
|
182 |
- return( DecontXoneBatch( omat = omat, z = z, max.iter = max.iter, beta = beta, delta = delta, logfile=logfile, verbose=verbose, seed=seed ) ) |
|
182 |
+ return( DecontXoneBatch( counts = counts, z = z, max.iter = max.iter, beta = beta, delta = delta, logfile=logfile, verbose=verbose, seed=seed ) ) |
|
183 | 183 |
|
184 | 184 |
} |
185 | 185 |
|
... | ... |
@@ -188,13 +188,13 @@ DecontX = function( omat , z=NULL, batch=NULL, max.iter=200, beta=1e-6, delta=1 |
188 | 188 |
|
189 | 189 |
# This function updates decontamination for one batch |
190 | 190 |
# |
191 |
-DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, delta=10, logfile=NULL, verbose=TRUE, seed=1234567 ) { |
|
191 |
+DecontXoneBatch = function(counts, z=NULL, batch= NULL, max.iter=200, beta=1e-6, delta=10, logfile=NULL, verbose=TRUE, seed=1234567 ) { |
|
192 | 192 |
|
193 |
- checkCounts.decon(omat) |
|
193 |
+ checkCounts.decon(counts) |
|
194 | 194 |
checkParameters.decon(proportion.prior=delta, distribution.prior=beta) |
195 | 195 |
|
196 |
- nG = nrow(omat) |
|
197 |
- nC = ncol(omat) |
|
196 |
+ nG = nrow(counts) |
|
197 |
+ nC = ncol(counts) |
|
198 | 198 |
K = length(unique(z)) |
199 | 199 |
|
200 | 200 |
if ( is.null(z) ) { |
... | ... |
@@ -225,7 +225,7 @@ DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, |
225 | 225 |
|
226 | 226 |
# Initialization |
227 | 227 |
theta = runif(nC, min = 0.1, max = 0.5) |
228 |
- est.rmat = t (t(omat) * theta ) |
|
228 |
+ est.rmat = t (t(counts) * theta ) |
|
229 | 229 |
phi = colSumByGroup.numeric(est.rmat, z, K) |
230 | 230 |
eta = rowSums(phi) - phi |
231 | 231 |
phi = normalizeCounts(phi, normalize="proportion", pseudocount.normalize =beta ) |
... | ... |
@@ -233,14 +233,14 @@ DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, |
233 | 233 |
ll = c() |
234 | 234 |
|
235 | 235 |
|
236 |
- ll.round = decon.calcLL(omat=omat, z=z, phi = phi, eta = eta, theta=theta ) |
|
236 |
+ ll.round = decon.calcLL(counts=counts, z=z, phi = phi, eta = eta, theta=theta ) |
|
237 | 237 |
|
238 | 238 |
|
239 | 239 |
# EM updates |
240 | 240 |
while (iter <= max.iter & num.iter.without.improvement <= stop.iter ) { |
241 | 241 |
|
242 | 242 |
|
243 |
- next.decon = cD.calcEMDecontamination(omat=omat, phi=phi, eta=eta, theta=theta, z=z, K=K, beta=beta, delta=delta) |
|
243 |
+ next.decon = cD.calcEMDecontamination(counts=counts, phi=phi, eta=eta, theta=theta, z=z, K=K, beta=beta, delta=delta) |
|
244 | 244 |
|
245 | 245 |
theta = next.decon$theta |
246 | 246 |
phi = next.decon$phi |
... | ... |
@@ -248,7 +248,7 @@ DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, |
248 | 248 |
delta = next.decon$delta |
249 | 249 |
|
250 | 250 |
# Calculate log-likelihood |
251 |
- ll.temp = decon.calcLL(omat=omat, z=z, phi = phi, eta = eta, theta=theta ) |
|
251 |
+ ll.temp = decon.calcLL(counts=counts, z=z, phi = phi, eta = eta, theta=theta ) |
|
252 | 252 |
ll = c(ll, ll.temp) |
253 | 253 |
ll.round = c( ll.round, round( ll.temp, 2) ) |
254 | 254 |
|
... | ... |
@@ -267,27 +267,27 @@ DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, |
267 | 267 |
|
268 | 268 |
# Initialization |
269 | 269 |
theta = runif( nC, min =0.1, max=0.5) |
270 |
- est.rmat = t( t(omat) *theta) |
|
271 |
- bgDist = rowSums( omat ) / sum( omat) |
|
270 |
+ est.rmat = t( t(counts) *theta) |
|
271 |
+ bgDist = rowSums( counts ) / sum( counts) |
|
272 | 272 |
bgDist = matrix( rep( bgDist, nC), ncol=nC) |
273 | 273 |
cellDist = normalizeCounts( est.rmat, normalize="proportion", pseudocount.normalize=beta) |
274 | 274 |
ll =c() |
275 | 275 |
|
276 | 276 |
|
277 |
- ll.round = bg.calcLL(omat=omat, cellDist=cellDist, bgDist=bgDist, theta=theta) |
|
277 |
+ ll.round = bg.calcLL(counts=counts, cellDist=cellDist, bgDist=bgDist, theta=theta) |
|
278 | 278 |
|
279 | 279 |
|
280 | 280 |
# EM updates |
281 | 281 |
while (iter <= max.iter & num.iter.without.improvement <= stop.iter ) { |
282 | 282 |
|
283 | 283 |
|
284 |
- next.decon = cD.calcEMbgDecontamination(omat=omat, cellDist=cellDist, bgDist=bgDist, theta=theta, beta=beta, delta=delta) |
|
284 |
+ next.decon = cD.calcEMbgDecontamination(counts=counts, cellDist=cellDist, bgDist=bgDist, theta=theta, beta=beta, delta=delta) |
|
285 | 285 |
|
286 | 286 |
theta = next.decon$theta |
287 | 287 |
cellDist = next.decon$cellDist |
288 | 288 |
|
289 | 289 |
# Calculate log-likelihood |
290 |
- ll.temp = bg.calcLL(omat=omat, cellDist=cellDist, bgDist=bgDist, theta=theta) |
|
290 |
+ ll.temp = bg.calcLL(counts=counts, cellDist=cellDist, bgDist=bgDist, theta=theta) |
|
291 | 291 |
ll = c(ll, ll.temp) |
292 | 292 |
ll.round = c( ll.round, round( ll.temp, 2) ) |
293 | 293 |
|
... | ... |
@@ -301,7 +301,7 @@ DecontXoneBatch = function(omat, z=NULL, batch= NULL, max.iter=200, beta=1e-6, |
301 | 301 |
|
302 | 302 |
} |
303 | 303 |
|
304 |
- res.conp = 1- colSums(next.decon$est.rmat) / colSums(omat) |
|
304 |
+ res.conp = 1- colSums(next.decon$est.rmat) / colSums(counts) |
|
305 | 305 |
|
306 | 306 |
|
307 | 307 |
end.time = Sys.time() |
... | ... |
@@ -334,9 +334,9 @@ checkParameters.decon = function(proportion.prior, distribution.prior) { |
334 | 334 |
} |
335 | 335 |
|
336 | 336 |
# Make sure provided rmat is the right type |
337 |
-checkCounts.decon = function(omat) { |
|
338 |
- if ( sum(is.na(omat)) >0 ) { |
|
339 |
- stop("Missing value in 'omat' matrix.") |
|
337 |
+checkCounts.decon = function(counts) { |
|
338 |
+ if ( sum(is.na(counts)) >0 ) { |
|
339 |
+ stop("Missing value in 'counts' matrix.") |
|
340 | 340 |
} |
341 | 341 |
} |
342 | 342 |
|
... | ... |
@@ -38,7 +38,7 @@ An analysis example using celda with RNASeq via vignette('celda-analysis') |
38 | 38 |
Highly expressed genes from various cells clusters will be expressed at low levels in other clusters in droplet-based systems due to contamination. DecontX will decompose an observed count matrix into a decontaminated expression matrix and a contamination matrix. The only other parameter needed is a vector of cell cluster labels. |
39 | 39 |
|
40 | 40 |
``` |
41 |
-new.counts = DecontX( omat = counts, z = cell.label) |
|
41 |
+new.counts = DecontX( counts = counts, z = cell.label) |
|
42 | 42 |
# Decontaminated matrix: new.counts$res.list$est.rmat |
43 | 43 |
# Percentage of contamination per cell: new.counts$res.list$est.conp |
44 | 44 |
``` |
... | ... |
@@ -4,11 +4,12 @@ |
4 | 4 |
\alias{DecontX} |
5 | 5 |
\title{This function updates decontamination on dataset with multiple batches} |
6 | 6 |
\usage{ |
7 |
-DecontX(omat, z = NULL, batch = NULL, max.iter = 200, beta = 1e-06, |
|
8 |
- delta = 10, logfile = NULL, verbose = TRUE, seed = 1234567) |
|
7 |
+DecontX(counts, z = NULL, batch = NULL, max.iter = 200, |
|
8 |
+ beta = 1e-06, delta = 10, logfile = NULL, verbose = TRUE, |
|
9 |
+ seed = 1234567) |
|
9 | 10 |
} |
10 | 11 |
\arguments{ |
11 |
-\item{omat}{Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells.} |
|
12 |
+\item{counts}{Numeric/Integer matrix. Observed count matrix, rows represent features and columns represent cells.} |
|
12 | 13 |
|
13 | 14 |
\item{z}{Integer vector. Cell population labels. Default NULL} |
14 | 15 |
|
... | ... |
@@ -30,6 +31,6 @@ DecontX(omat, z = NULL, batch = NULL, max.iter = 200, beta = 1e-06, |
30 | 31 |
This function updates decontamination on dataset with multiple batches |
31 | 32 |
} |
32 | 33 |
\examples{ |
33 |
-decon.c = DecontX( omat = contamination.sim$rmat + contamination.sim$cmat, z=contamination.sim$z, max.iter=3) |
|
34 |
-decon.bg = DecontX( omat=contamination.sim$rmat + contamination.sim$cmat, max.iter=3 ) |
|
34 |
+decon.c = DecontX( counts = contamination.sim$rmat + contamination.sim$cmat, z=contamination.sim$z, max.iter=3) |
|
35 |
+decon.bg = DecontX( counts=contamination.sim$rmat + contamination.sim$cmat, max.iter=3 ) |
|
35 | 36 |
} |
... | ... |
@@ -41,16 +41,16 @@ |
41 | 41 |
test_that( desc = "Testing DecontXoneBatch", { |
42 | 42 |
expect_equal( model_DecontXoneBatch$res.list$est.conp , 1 - colSums(model_DecontXoneBatch$res.list$est.rmat) / colSums( Decon.sim$rmat + Decon.sim$cmat) ) |
43 | 43 |
expect_equal( model_DecontXoneBatch$res.list$theta, (model_DecontXoneBatch$run.params$delta + colSums(model_DecontXoneBatch$res.list$est.rmat) ) / ( 2*model_DecontXoneBatch$run.params$delta + colSums(Decon.sim$cmat + Decon.sim$rmat) ) ) |
44 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, beta=-1), "'beta' should be a single positive value.") |
|
45 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, beta=c(1,1) ), "'beta' should be a single positive value.") |
|
46 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, delta=-1), "'delta' should be a single positive value.") |
|
47 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, delta=c(1,1) ), "'delta' should be a single positive value.") |
|
48 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=c(Decon.sim$z, 1) ), "'z' must be of the same length as the number of cells in the 'counts' matrix.") |
|
49 |
- expect_error( DecontXoneBatch(omat=Decon.sim$rmat+Decon.sim$cmat, z=rep(1, ncol(Decon.sim$rmat)) ), "'z' must have at least 2 different values.") |
|
50 |
- |
|
51 |
- omat.NA = Decon.sim$rmat + Decon.sim$cmat |
|
52 |
- omat.NA[1,1] = NA |
|
53 |
- expect_error( DecontXoneBatch(omat=omat.NA, z=Decon.sim$z), "Missing value in 'omat' matrix.") |
|
44 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, beta=-1), "'beta' should be a single positive value.") |
|
45 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, beta=c(1,1) ), "'beta' should be a single positive value.") |
|
46 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, delta=-1), "'delta' should be a single positive value.") |
|
47 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=Decon.sim$z, delta=c(1,1) ), "'delta' should be a single positive value.") |
|
48 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=c(Decon.sim$z, 1) ), "'z' must be of the same length as the number of cells in the 'counts' matrix.") |
|
49 |
+ expect_error( DecontXoneBatch(counts=Decon.sim$rmat+Decon.sim$cmat, z=rep(1, ncol(Decon.sim$rmat)) ), "'z' must have at least 2 different values.") |
|
50 |
+ |
|
51 |
+ counts.NA = Decon.sim$rmat + Decon.sim$cmat |
|
52 |
+ counts.NA[1,1] = NA |
|
53 |
+ expect_error( DecontXoneBatch(counts=counts.NA, z=Decon.sim$z), "Missing value in 'counts' matrix.") |
|
54 | 54 |
} ) |
55 | 55 |
|
56 | 56 |
test_that( desc = " Testing DecontXoneBatch using background distribution", { |
... | ... |
@@ -61,18 +61,18 @@ |
61 | 61 |
# logLikelihood |
62 | 62 |
test_that( desc = "Testing logLikelihood.DecontXoneBatch", { |
63 | 63 |
z.process = processCellLabels(Decon.sim$z, num.cells=ncol(Decon.sim$rmat) ) |
64 |
- expect_equal( decon.calcLL(omat=Decon.sim$cmat+Decon.sim$rmat, z=z.process , theta=model_DecontXoneBatch$res.list$theta, eta=model_DecontXoneBatch$res.list$est.ConDist, phi=model_DecontXoneBatch$res.list$est.GeneDist ), model_DecontXoneBatch$res.list$logLikelihood[ model_DecontXoneBatch$run.params$iteration ] ) |
|
64 |
+ expect_equal( decon.calcLL(counts=Decon.sim$cmat+Decon.sim$rmat, z=z.process , theta=model_DecontXoneBatch$res.list$theta, eta=model_DecontXoneBatch$res.list$est.ConDist, phi=model_DecontXoneBatch$res.list$est.GeneDist ), model_DecontXoneBatch$res.list$logLikelihood[ model_DecontXoneBatch$run.params$iteration ] ) |
|
65 | 65 |
|
66 | 66 |
cellDist.model.bg = normalizeCounts( model_DecontXoneBatchbg$res.list$est.rmat, normalize="proportion", pseudocount.normalize= model_DecontXoneBatchbg$run.params$beta) |
67 | 67 |
bgDist.model.bg = rowSums( Decon.sim$rmat+ Decon.sim$cmat) / sum( Decon.sim$N.by.C) |
68 | 68 |
bgDist.model.bg = matrix( rep(bgDist.model.bg, length(Decon.sim$N.by.C) ), ncol= length(Decon.sim$N.by.C) ) |
69 |
- expect_equal( bg.calcLL( omat=Decon.sim$cmat+Decon.sim$rmat, theta=model_DecontXoneBatchbg$res.list$theta, cellDist= cellDist.model.bg, bgDist= bgDist.model.bg), model_DecontXoneBatchbg$res.list$logLikelihood[ model_DecontXoneBatchbg$run.params$iteration ] ) |
|
69 |
+ expect_equal( bg.calcLL( counts=Decon.sim$cmat+Decon.sim$rmat, theta=model_DecontXoneBatchbg$res.list$theta, cellDist= cellDist.model.bg, bgDist= bgDist.model.bg), model_DecontXoneBatchbg$res.list$logLikelihood[ model_DecontXoneBatchbg$run.params$iteration ] ) |
|
70 | 70 |
} ) |
71 | 71 |
|
72 | 72 |
# decontamination EM updates |
73 | 73 |
test_that( desc = "Testing decontamination EM updates", { |
74 | 74 |
z.process = processCellLabels(Decon.sim$z, num.cells=ncol(Decon.sim$rmat) ) |
75 |
- expect_equal( cD.calcEMDecontamination( omat=Decon.sim$cmat+Decon.sim$rmat, z=z.process, K=length(unique(Decon.sim$z)), theta=model_DecontXoneBatch.iter1$res.list$theta, phi=model_DecontXoneBatch.iter1$res.list$est.GeneDist, eta=model_DecontXoneBatch.iter1$res.list$est.ConDist, beta=model_DecontXoneBatch.iter1$run.params$beta, delta=model_DecontXoneBatch.iter1$run.params$delta)$theta, model_DecontXoneBatch$res.list$theta ) |
|
75 |
+ expect_equal( cD.calcEMDecontamination( counts=Decon.sim$cmat+Decon.sim$rmat, z=z.process, K=length(unique(Decon.sim$z)), theta=model_DecontXoneBatch.iter1$res.list$theta, phi=model_DecontXoneBatch.iter1$res.list$est.GeneDist, eta=model_DecontXoneBatch.iter1$res.list$est.ConDist, beta=model_DecontXoneBatch.iter1$run.params$beta, delta=model_DecontXoneBatch.iter1$run.params$delta)$theta, model_DecontXoneBatch$res.list$theta ) |
|
76 | 76 |
} ) |
77 | 77 |
|
78 | 78 |
|