... | ... |
@@ -11,7 +11,7 @@ |
11 | 11 |
#' Rows represent features and columns represent cells. Alternatively, |
12 | 12 |
#' any matrix-like object that can be coerced to a sparse matrix of class |
13 | 13 |
#' "dgCMatrix" can be directly used as input. The matrix will automatically be |
14 |
-#' converted to a \linkS4class{SingleCellExperiment} object. |
|
14 |
+#' converted to a \linkS4class{SingleCellExperiment} object. |
|
15 | 15 |
#' @param useAssay A string specifying the name of the |
16 | 16 |
#' \link{assay} slot to use. Default "counts". |
17 | 17 |
#' @param altExpName The name for the \link{altExp} slot |
... | ... |
@@ -173,7 +173,7 @@ setMethod("celda_G", |
173 | 173 |
|
174 | 174 |
# Convert to sparse matrix |
175 | 175 |
x <- methods::as(x, "dgCMatrix") |
176 |
- |
|
176 |
+ |
|
177 | 177 |
ls <- list() |
178 | 178 |
ls[[useAssay]] <- x |
179 | 179 |
sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
... | ... |
@@ -6,10 +6,12 @@ |
6 | 6 |
#' it exists. Otherwise, the \code{useAssay} |
7 | 7 |
#' \link{assay} slot in \code{x} will be used if |
8 | 8 |
#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
9 |
-#' @param x A numeric \link{matrix} of counts or a |
|
10 |
-#' \linkS4class{SingleCellExperiment} |
|
9 |
+#' @param x A \linkS4class{SingleCellExperiment} |
|
11 | 10 |
#' with the matrix located in the assay slot under \code{useAssay}. |
12 |
-#' Rows represent features and columns represent cells. |
|
11 |
+#' Rows represent features and columns represent cells. Alternatively, |
|
12 |
+#' any matrix-like object that can be coerced to a sparse matrix of class |
|
13 |
+#' "dgCMatrix" can be directly used as input. The matrix will automatically be |
|
14 |
+#' converted to a \linkS4class{SingleCellExperiment} object. |
|
13 | 15 |
#' @param useAssay A string specifying the name of the |
14 | 16 |
#' \link{assay} slot to use. Default "counts". |
15 | 17 |
#' @param altExpName The name for the \link{altExp} slot |
... | ... |
@@ -149,7 +151,7 @@ setMethod("celda_G", |
149 | 151 |
#' @rdname celda_G |
150 | 152 |
#' @export |
151 | 153 |
setMethod("celda_G", |
152 |
- signature(x = "matrix"), |
|
154 |
+ signature(x = "ANY"), |
|
153 | 155 |
function(x, |
154 | 156 |
useAssay = "counts", |
155 | 157 |
altExpName = "featureSubset", |
... | ... |
@@ -169,6 +171,9 @@ setMethod("celda_G", |
169 | 171 |
logfile = NULL, |
170 | 172 |
verbose = TRUE) { |
171 | 173 |
|
174 |
+ # Convert to sparse matrix |
|
175 |
+ x <- as(x, "dgCMatrix") |
|
176 |
+ |
|
172 | 177 |
ls <- list() |
173 | 178 |
ls[[useAssay]] <- x |
174 | 179 |
sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
... | ... |
@@ -753,7 +753,7 @@ setMethod("celda_G", |
753 | 753 |
|
754 | 754 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
755 | 755 |
counts <- .processCounts(counts) |
756 |
- y <- SummarizedExperiment::rowData(sce)$celda_feature_module |
|
756 |
+ y <- as.integer(SummarizedExperiment::rowData(sce)$celda_feature_module) |
|
757 | 757 |
L <- S4Vectors::metadata(sce)$celda_parameters$L |
758 | 758 |
beta <- S4Vectors::metadata(sce)$celda_parameters$beta |
759 | 759 |
delta <- S4Vectors::metadata(sce)$celda_parameters$delta |
... | ... |
@@ -753,6 +753,13 @@ setMethod("celda_G", |
753 | 753 |
|
754 | 754 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
755 | 755 |
counts <- .processCounts(counts) |
756 |
+ y <- SummarizedExperiment::rowData(sce)$celda_feature_module |
|
757 |
+ L <- S4Vectors::metadata(sce)$celda_parameters$L |
|
758 |
+ beta <- S4Vectors::metadata(sce)$celda_parameters$beta |
|
759 |
+ delta <- S4Vectors::metadata(sce)$celda_parameters$delta |
|
760 |
+ gamma <- S4Vectors::metadata(sce)$celda_parameters$gamma |
|
761 |
+ cNames <- colnames(sce) |
|
762 |
+ rNames <- rownames(sce) |
|
756 | 763 |
|
757 | 764 |
if (is.null(maxCells) || maxCells > ncol(counts)) { |
758 | 765 |
maxCells <- ncol(counts) |
... | ... |
@@ -761,7 +768,16 @@ setMethod("celda_G", |
761 | 768 |
cellIx <- sample(seq(ncol(counts)), maxCells) |
762 | 769 |
} |
763 | 770 |
|
764 |
- fm <- factorizeMatrix(x = sce, useAssay = useAssay, type = "counts") |
|
771 |
+ fm <- .factorizeMatrixG( |
|
772 |
+ counts = counts, |
|
773 |
+ y = y, |
|
774 |
+ L = L, |
|
775 |
+ beta = beta, |
|
776 |
+ delta = delta, |
|
777 |
+ gamma = gamma, |
|
778 |
+ cNames = cNames, |
|
779 |
+ rNames = rNames, |
|
780 |
+ type = "counts") |
|
765 | 781 |
|
766 | 782 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
767 | 783 |
if (!is.null(modules)) { |
... | ... |
@@ -48,9 +48,8 @@ |
48 | 48 |
#' @param countChecksum Character. An MD5 checksum for the `counts` matrix. |
49 | 49 |
#' Default NULL. |
50 | 50 |
#' @param logfile Character. Messages will be redirected to a file named |
51 |
-#' `logfile`. If NULL, messages will be printed to stdout. Default NULL. |
|
51 |
+#' \code{logfile}. If NULL, messages will be printed to stdout. Default NULL. |
|
52 | 52 |
#' @param verbose Logical. Whether to print log messages. Default TRUE. |
53 |
-#' @param ... Ignored. Placeholder to prevent check warning. |
|
54 | 53 |
#' @return A \linkS4class{SingleCellExperiment} object. Function |
55 | 54 |
#' parameter settings are stored in the \link{metadata} |
56 | 55 |
#' \code{"celda_parameters"} slot. Column \code{celda_feature_module} in |
... | ... |
@@ -62,7 +61,25 @@ |
62 | 61 |
#' data(celdaGSim) |
63 | 62 |
#' sce <- celda_G(celdaGSim$counts, L = celdaGSim$L, nchains = 1) |
64 | 63 |
#' @export |
65 |
-setGeneric("celda_G", function(x, ...) { |
|
64 |
+setGeneric("celda_G", |
|
65 |
+ function(x, |
|
66 |
+ useAssay = "counts", |
|
67 |
+ altExpName = "featureSubset", |
|
68 |
+ L, |
|
69 |
+ beta = 1, |
|
70 |
+ delta = 1, |
|
71 |
+ gamma = 1, |
|
72 |
+ stopIter = 10, |
|
73 |
+ maxIter = 200, |
|
74 |
+ splitOnIter = 10, |
|
75 |
+ splitOnLast = TRUE, |
|
76 |
+ seed = 12345, |
|
77 |
+ nchains = 3, |
|
78 |
+ yInitialize = c("split", "random", "predefined"), |
|
79 |
+ countChecksum = NULL, |
|
80 |
+ yInit = NULL, |
|
81 |
+ logfile = NULL, |
|
82 |
+ verbose = TRUE) { |
|
66 | 83 |
standardGeneric("celda_G")}) |
67 | 84 |
|
68 | 85 |
|
... | ... |
@@ -744,7 +744,7 @@ setMethod("celda_G", |
744 | 744 |
cellIx <- sample(seq(ncol(counts)), maxCells) |
745 | 745 |
} |
746 | 746 |
|
747 |
- fm <- .factorizeMatrixCelda_G(sce, useAssay = useAssay, type = "counts") |
|
747 |
+ fm <- factorizeMatrix(x = sce, useAssay = useAssay, type = "counts") |
|
748 | 748 |
|
749 | 749 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
750 | 750 |
if (!is.null(modules)) { |
... | ... |
@@ -813,7 +813,7 @@ setMethod("celda_G", |
813 | 813 |
SummarizedExperiment::colData(sce)["colnames"] <- |
814 | 814 |
celdaGMod@names$column |
815 | 815 |
SummarizedExperiment::rowData(sce)["celda_feature_module"] <- |
816 |
- celdaClusters(celdaGMod)$y |
|
816 |
+ as.factor(celdaClusters(celdaGMod)$y) |
|
817 | 817 |
|
818 | 818 |
return(sce) |
819 | 819 |
} |
... | ... |
@@ -295,7 +295,7 @@ setMethod("celda_G", |
295 | 295 |
start.time <- Sys.time() |
296 | 296 |
|
297 | 297 |
## Error checking and variable processing |
298 |
- #counts <- .processCounts(counts) |
|
298 |
+ counts <- .processCounts(counts) |
|
299 | 299 |
if (is.null(countChecksum)) { |
300 | 300 |
countChecksum <- .createCountChecksum(counts) |
301 | 301 |
} |
... | ... |
@@ -260,7 +260,7 @@ setMethod("celda_G", |
260 | 260 |
return(sce) |
261 | 261 |
} |
262 | 262 |
|
263 |
- |
|
263 |
+#' @importFrom Matrix colSums |
|
264 | 264 |
.celda_G <- function(counts, |
265 | 265 |
L, |
266 | 266 |
beta = 1, |
... | ... |
@@ -304,12 +304,7 @@ setMethod("celda_G", |
304 | 304 |
allChains <- seq(nchains) |
305 | 305 |
|
306 | 306 |
# Pre-compute lgamma values |
307 |
- if(inherits(counts, "dgCMatrix")) { |
|
308 |
- cs <- Matrix::colSums(counts) |
|
309 |
- } else { |
|
310 |
- cs <- .colSums(counts, nrow(counts), ncol(counts)) |
|
311 |
- } |
|
312 |
- |
|
307 |
+ cs <- colSums(counts) |
|
313 | 308 |
lgbeta <- lgamma(seq(0, max(cs)) + beta) |
314 | 309 |
lggamma <- lgamma(seq(0, nrow(counts) + L) + gamma) |
315 | 310 |
lgdelta <- c(NA, lgamma((seq(nrow(counts) + L) * delta))) |
... | ... |
@@ -603,7 +598,7 @@ setMethod("celda_G", |
603 | 598 |
ix <- sample(seq(nG)) |
604 | 599 |
for (i in ix) { |
605 | 600 |
probs[, i] <- cG_CalcGibbsProbY(index = i, |
606 |
- counts = as.numeric(counts[i,]), |
|
601 |
+ counts = as.numeric(counts[i, ]), |
|
607 | 602 |
nTSbyC = nTSByC, |
608 | 603 |
nbyTS = nByTS, |
609 | 604 |
nGbyTS = nGByTS, |
... | ... |
@@ -691,19 +686,15 @@ setMethod("celda_G", |
691 | 686 |
# cells. |
692 | 687 |
# @param y Numeric vector. Denotes feature module labels. |
693 | 688 |
# @param L Integer. Number of feature modules. |
689 |
+#' @importFrom Matrix rowSums |
|
694 | 690 |
.cGDecomposeCounts <- function(counts, y, L) { |
695 | 691 |
if (any(y > L)) { |
696 | 692 |
stop("Assigned value of feature module greater than the total number", |
697 | 693 |
" of feature modules!") |
698 | 694 |
} |
699 |
- |
|
695 |
+ |
|
700 | 696 |
nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
701 |
- |
|
702 |
- if (inherits(counts, "dgCMatrix")) { |
|
703 |
- nByG <- as.integer(Matrix::rowSums(counts)) |
|
704 |
- } else { |
|
705 |
- nByG <- .rowSums(counts, nrow(counts), ncol(counts)) |
|
706 |
- } |
|
697 |
+ nByG <- rowSums(counts) |
|
707 | 698 |
nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
708 | 699 |
nGByTS <- tabulate(y, L) + 1 ## Add pseudogene to each state |
709 | 700 |
nM <- ncol(counts) |
... | ... |
@@ -722,7 +713,6 @@ setMethod("celda_G", |
722 | 713 |
|
723 | 714 |
.cGReDecomposeCounts <- function(counts, y, previousY, nTSByC, nByG, L) { |
724 | 715 |
## Recalculate counts based on new label |
725 |
- |
|
726 | 716 |
nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
727 | 717 |
nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
728 | 718 |
nGByTS <- tabulate(y, L) + 1 |
... | ... |
@@ -295,7 +295,7 @@ setMethod("celda_G", |
295 | 295 |
start.time <- Sys.time() |
296 | 296 |
|
297 | 297 |
## Error checking and variable processing |
298 |
- counts <- .processCounts(counts) |
|
298 |
+ #counts <- .processCounts(counts) |
|
299 | 299 |
if (is.null(countChecksum)) { |
300 | 300 |
countChecksum <- .createCountChecksum(counts) |
301 | 301 |
} |
... | ... |
@@ -304,10 +304,13 @@ setMethod("celda_G", |
304 | 304 |
allChains <- seq(nchains) |
305 | 305 |
|
306 | 306 |
# Pre-compute lgamma values |
307 |
- lgbeta <- lgamma(seq(0, max(.colSums( |
|
308 |
- counts, |
|
309 |
- nrow(counts), ncol(counts) |
|
310 |
- ))) + beta) |
|
307 |
+ if(inherits(counts, "dgCMatrix")) { |
|
308 |
+ cs <- Matrix::colSums(counts) |
|
309 |
+ } else { |
|
310 |
+ cs <- .colSums(counts, nrow(counts), ncol(counts)) |
|
311 |
+ } |
|
312 |
+ |
|
313 |
+ lgbeta <- lgamma(seq(0, max(cs)) + beta) |
|
311 | 314 |
lggamma <- lgamma(seq(0, nrow(counts) + L) + gamma) |
312 | 315 |
lgdelta <- c(NA, lgamma((seq(nrow(counts) + L) * delta))) |
313 | 316 |
|
... | ... |
@@ -694,25 +697,14 @@ setMethod("celda_G", |
694 | 697 |
" of feature modules!") |
695 | 698 |
} |
696 | 699 |
|
697 |
- if (inherits(counts, "matrix") & is.integer(counts)) { |
|
698 |
- nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
|
699 |
- nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
|
700 |
- nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), |
|
701 |
- group = y, L = L)) |
|
702 |
- } else if (inherits(counts, "matrix") & is.numeric(counts)) { |
|
703 |
- nTSByC <- .rowSumByGroupNumeric(counts, group = y, L = L) |
|
704 |
- nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
|
705 |
- nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), |
|
706 |
- group = y, L = L) |
|
707 |
- } else if (inherits(counts, "dgCMatrix")) { |
|
708 |
- nTSByC <- rowSumByGroupSparse(counts, group = y) |
|
700 |
+ nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
|
701 |
+ |
|
702 |
+ if (inherits(counts, "dgCMatrix")) { |
|
709 | 703 |
nByG <- as.integer(Matrix::rowSums(counts)) |
710 |
- nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), |
|
711 |
- group = y, L = L) |
|
712 | 704 |
} else { |
713 |
- stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
|
705 |
+ nByG <- .rowSums(counts, nrow(counts), ncol(counts)) |
|
714 | 706 |
} |
715 |
- |
|
707 |
+ nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
|
716 | 708 |
nGByTS <- tabulate(y, L) + 1 ## Add pseudogene to each state |
717 | 709 |
nM <- ncol(counts) |
718 | 710 |
nG <- nrow(counts) |
... | ... |
@@ -730,18 +722,9 @@ setMethod("celda_G", |
730 | 722 |
|
731 | 723 |
.cGReDecomposeCounts <- function(counts, y, previousY, nTSByC, nByG, L) { |
732 | 724 |
## Recalculate counts based on new label |
733 |
- if (inherits(counts, "matrix") & is.integer(counts)) { |
|
734 |
- nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
|
735 |
- nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
|
736 |
- } else if (inherits(counts, "matrix") & is.numeric(counts)) { |
|
737 |
- nTSByC <- .rowSumByGroupChangeNumeric(counts, nTSByC, y, previousY, L) |
|
738 |
- nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), group = y, L = L) |
|
739 |
- } else if (inherits(counts, "dgCMatrix")) { |
|
740 |
- nTSByC <- rowSumByGroupChangeSparse(counts, nTSByC, y, previousY) |
|
741 |
- nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), group = y, L = L) |
|
742 |
- } else { |
|
743 |
- stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
|
744 |
- } |
|
725 |
+ |
|
726 |
+ nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
|
727 |
+ nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
|
745 | 728 |
nGByTS <- tabulate(y, L) + 1 |
746 | 729 |
|
747 | 730 |
return(list( |
... | ... |
@@ -697,16 +697,22 @@ setMethod("celda_G", |
697 | 697 |
if (inherits(counts, "matrix") & is.integer(counts)) { |
698 | 698 |
nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
699 | 699 |
nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
700 |
+ nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), |
|
701 |
+ group = y, L = L)) |
|
700 | 702 |
} else if (inherits(counts, "matrix") & is.numeric(counts)) { |
701 | 703 |
nTSByC <- .rowSumByGroupNumeric(counts, group = y, L = L) |
702 | 704 |
nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
705 |
+ nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), |
|
706 |
+ group = y, L = L) |
|
703 | 707 |
} else if (inherits(counts, "dgCMatrix")) { |
704 | 708 |
nTSByC <- rowSumByGroupSparse(counts, group = y) |
705 | 709 |
nByG <- as.integer(Matrix::rowSums(counts)) |
710 |
+ nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), |
|
711 |
+ group = y, L = L) |
|
706 | 712 |
} else { |
707 | 713 |
stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
708 | 714 |
} |
709 |
- nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1),group = y, L = L)) |
|
715 |
+ |
|
710 | 716 |
nGByTS <- tabulate(y, L) + 1 ## Add pseudogene to each state |
711 | 717 |
nM <- ncol(counts) |
712 | 718 |
nG <- nrow(counts) |
... | ... |
@@ -726,15 +732,16 @@ setMethod("celda_G", |
726 | 732 |
## Recalculate counts based on new label |
727 | 733 |
if (inherits(counts, "matrix") & is.integer(counts)) { |
728 | 734 |
nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
735 |
+ nByTS <- .rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L) |
|
729 | 736 |
} else if (inherits(counts, "matrix") & is.numeric(counts)) { |
730 | 737 |
nTSByC <- .rowSumByGroupChangeNumeric(counts, nTSByC, y, previousY, L) |
738 |
+ nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), group = y, L = L) |
|
731 | 739 |
} else if (inherits(counts, "dgCMatrix")) { |
732 |
- nTSByC <- rowSumByGroupChangeSparse(counts, nTSByC, y, previousY) |
|
740 |
+ nTSByC <- rowSumByGroupChangeSparse(counts, nTSByC, y, previousY) |
|
741 |
+ nByTS <- .rowSumByGroupNumeric(matrix(nByG, ncol = 1), group = y, L = L) |
|
733 | 742 |
} else { |
734 | 743 |
stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
735 | 744 |
} |
736 |
- |
|
737 |
- nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L)) |
|
738 | 745 |
nGByTS <- tabulate(y, L) + 1 |
739 | 746 |
|
740 | 747 |
return(list( |
... | ... |
@@ -693,11 +693,20 @@ setMethod("celda_G", |
693 | 693 |
stop("Assigned value of feature module greater than the total number", |
694 | 694 |
" of feature modules!") |
695 | 695 |
} |
696 |
- nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
|
697 |
- nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
|
698 |
- nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), |
|
699 |
- group = y, L = L |
|
700 |
- )) |
|
696 |
+ |
|
697 |
+ if (inherits(counts, "matrix") & is.integer(counts)) { |
|
698 |
+ nTSByC <- .rowSumByGroup(counts, group = y, L = L) |
|
699 |
+ nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
|
700 |
+ } else if (inherits(counts, "matrix") & is.numeric(counts)) { |
|
701 |
+ nTSByC <- .rowSumByGroupNumeric(counts, group = y, L = L) |
|
702 |
+ nByG <- as.integer(.rowSums(counts, nrow(counts), ncol(counts))) |
|
703 |
+ } else if (inherits(counts, "dgCMatrix")) { |
|
704 |
+ nTSByC <- rowSumByGroupSparse(counts, group = y) |
|
705 |
+ nByG <- as.integer(Matrix::rowSums(counts)) |
|
706 |
+ } else { |
|
707 |
+ stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
|
708 |
+ } |
|
709 |
+ nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1),group = y, L = L)) |
|
701 | 710 |
nGByTS <- tabulate(y, L) + 1 ## Add pseudogene to each state |
702 | 711 |
nM <- ncol(counts) |
703 | 712 |
nG <- nrow(counts) |
... | ... |
@@ -715,10 +724,17 @@ setMethod("celda_G", |
715 | 724 |
|
716 | 725 |
.cGReDecomposeCounts <- function(counts, y, previousY, nTSByC, nByG, L) { |
717 | 726 |
## Recalculate counts based on new label |
718 |
- nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
|
719 |
- nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), |
|
720 |
- group = y, L = L |
|
721 |
- )) |
|
727 |
+ if (inherits(counts, "matrix") & is.integer(counts)) { |
|
728 |
+ nTSByC <- .rowSumByGroupChange(counts, nTSByC, y, previousY, L) |
|
729 |
+ } else if (inherits(counts, "matrix") & is.numeric(counts)) { |
|
730 |
+ nTSByC <- .rowSumByGroupChangeNumeric(counts, nTSByC, y, previousY, L) |
|
731 |
+ } else if (inherits(counts, "dgCMatrix")) { |
|
732 |
+ nTSByC <- rowSumByGroupChangeSparse(counts, nTSByC, y, previousY) |
|
733 |
+ } else { |
|
734 |
+ stop("'counts' must be an integer, numeric, or dgCMatrix matrix.") |
|
735 |
+ } |
|
736 |
+ |
|
737 |
+ nByTS <- as.integer(.rowSumByGroup(matrix(nByG, ncol = 1), group = y, L = L)) |
|
722 | 738 |
nGByTS <- tabulate(y, L) + 1 |
723 | 739 |
|
724 | 740 |
return(list( |
... | ... |
@@ -415,7 +415,7 @@ setMethod("celda_G", |
415 | 415 |
) |
416 | 416 |
if (L > 2 & iter != maxIter & |
417 | 417 |
((((numIterWithoutImprovement == stopIter & |
418 |
- !all(tempLl > ll))) & isTRUE(splitOnLast)) | |
|
418 |
+ !all(tempLl >= ll))) & isTRUE(splitOnLast)) | |
|
419 | 419 |
(splitOnIter > 0 & iter %% splitOnIter == 0 & |
420 | 420 |
isTRUE(doGeneSplit)))) { |
421 | 421 |
.logMessages(date(), |
... | ... |
@@ -599,9 +599,8 @@ setMethod("celda_G", |
599 | 599 |
probs <- matrix(NA, ncol = nG, nrow = L) |
600 | 600 |
ix <- sample(seq(nG)) |
601 | 601 |
for (i in ix) { |
602 |
- probs[, i] <- cG_CalcGibbsProbY( |
|
603 |
- index = i, |
|
604 |
- counts = counts, |
|
602 |
+ probs[, i] <- cG_CalcGibbsProbY(index = i, |
|
603 |
+ counts = as.numeric(counts[i,]), |
|
605 | 604 |
nTSbyC = nTSByC, |
606 | 605 |
nbyTS = nByTS, |
607 | 606 |
nGbyTS = nGByTS, |
... | ... |
@@ -43,7 +43,7 @@ |
43 | 43 |
#' features will be split into sqrt(L) modules and then each module will be |
44 | 44 |
#' subsequently split into another sqrt(L) modules. With 'predefined', values |
45 | 45 |
#' in `yInit` will be used to initialize `y`. Default 'split'. |
46 |
-#' @param yInit Integer vector. Sets initial starting values of y. |
|
46 |
+#' @param yInit Integer vector. Sets initial starting values of y. |
|
47 | 47 |
#' `yInit` can only be used when `yInitialize = 'predefined'`. Default NULL. |
48 | 48 |
#' @param countChecksum Character. An MD5 checksum for the `counts` matrix. |
49 | 49 |
#' Default NULL. |
... | ... |
@@ -43,9 +43,8 @@ |
43 | 43 |
#' features will be split into sqrt(L) modules and then each module will be |
44 | 44 |
#' subsequently split into another sqrt(L) modules. With 'predefined', values |
45 | 45 |
#' in `yInit` will be used to initialize `y`. Default 'split'. |
46 |
-#' @param yInit Integer vector. Sets initial starting values of y. If NULL, |
|
47 |
-#' starting values for each feature will be randomly sampled from `1:L`. |
|
48 |
-#' `yInit` can only be used when `initialize = 'random'`. Default NULL. |
|
46 |
+#' @param yInit Integer vector. Sets initial starting values of y. |
|
47 |
+#' `yInit` can only be used when `yInitialize = 'predefined'`. Default NULL. |
|
49 | 48 |
#' @param countChecksum Character. An MD5 checksum for the `counts` matrix. |
50 | 49 |
#' Default NULL. |
51 | 50 |
#' @param logfile Character. Messages will be redirected to a file named |
... | ... |
@@ -731,20 +731,6 @@ setMethod("celda_G", |
731 | 731 |
} |
732 | 732 |
|
733 | 733 |
|
734 |
-.reorderCeldaG <- function(counts, res) { |
|
735 |
- if (params(res)$L > 2 & isTRUE(length(unique(celdaClusters(res)$y)) > 1)) { |
|
736 |
- res@clusters$y <- as.integer(as.factor(celdaClusters(res)$y)) |
|
737 |
- fm <- factorizeMatrix(counts, res) |
|
738 |
- uniqueY <- sort(unique(celdaClusters(res)$y)) |
|
739 |
- cs <- prop.table(t(fm$posterior$cell[uniqueY, ]), 2) |
|
740 |
- d <- .cosineDist(cs) |
|
741 |
- h <- stats::hclust(d, method = "complete") |
|
742 |
- res <- .recodeClusterY(res, from = h$order, to = seq(length(h$order))) |
|
743 |
- } |
|
744 |
- return(res) |
|
745 |
-} |
|
746 |
- |
|
747 |
- |
|
748 | 734 |
.prepareCountsForDimReductionCeldaG <- function(sce, |
749 | 735 |
useAssay, |
750 | 736 |
maxCells, |
... | ... |
@@ -1,18 +1,18 @@ |
1 | 1 |
#' @title Feature clustering with Celda |
2 | 2 |
#' @description Clusters the rows of a count matrix containing single-cell data |
3 | 3 |
#' into L modules. The |
4 |
-#' \code{useAssay} \link[SummarizedExperiment]{assay} slot in |
|
5 |
-#' \code{altExpName} \link[SingleCellExperiment]{altExp} slot will be used if |
|
4 |
+#' \code{useAssay} \link{assay} slot in |
|
5 |
+#' \code{altExpName} \link{altExp} slot will be used if |
|
6 | 6 |
#' it exists. Otherwise, the \code{useAssay} |
7 |
-#' \link[SummarizedExperiment]{assay} slot in \code{x} will be used if |
|
7 |
+#' \link{assay} slot in \code{x} will be used if |
|
8 | 8 |
#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
9 | 9 |
#' @param x A numeric \link{matrix} of counts or a |
10 | 10 |
#' \linkS4class{SingleCellExperiment} |
11 | 11 |
#' with the matrix located in the assay slot under \code{useAssay}. |
12 | 12 |
#' Rows represent features and columns represent cells. |
13 | 13 |
#' @param useAssay A string specifying the name of the |
14 |
-#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
15 |
-#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
14 |
+#' \link{assay} slot to use. Default "counts". |
|
15 |
+#' @param altExpName The name for the \link{altExp} slot |
|
16 | 16 |
#' to use. Default "featureSubset". |
17 | 17 |
#' @param L Integer. Number of feature modules. |
18 | 18 |
#' @param beta Numeric. Concentration parameter for Phi. Adds a pseudocount to |
... | ... |
@@ -53,9 +53,9 @@ |
53 | 53 |
#' @param verbose Logical. Whether to print log messages. Default TRUE. |
54 | 54 |
#' @param ... Ignored. Placeholder to prevent check warning. |
55 | 55 |
#' @return A \linkS4class{SingleCellExperiment} object. Function |
56 |
-#' parameter settings are stored in the \link[S4Vectors]{metadata} |
|
56 |
+#' parameter settings are stored in the \link{metadata} |
|
57 | 57 |
#' \code{"celda_parameters"} slot. Column \code{celda_feature_module} in |
58 |
-#' \link[SummarizedExperiment]{rowData} contains feature modules. |
|
58 |
+#' \link{rowData} contains feature modules. |
|
59 | 59 |
#' @seealso \link{celda_C} for cell clustering and \link{celda_CG} for |
60 | 60 |
#' simultaneous clustering of features and cells. \link{celdaGridSearch} can |
61 | 61 |
#' be used to run multiple values of L and multiple chains in parallel. |
... | ... |
@@ -51,6 +51,7 @@ |
51 | 51 |
#' @param logfile Character. Messages will be redirected to a file named |
52 | 52 |
#' `logfile`. If NULL, messages will be printed to stdout. Default NULL. |
53 | 53 |
#' @param verbose Logical. Whether to print log messages. Default TRUE. |
54 |
+#' @param ... Ignored. Placeholder to prevent check warning. |
|
54 | 55 |
#' @return A \linkS4class{SingleCellExperiment} object. Function |
55 | 56 |
#' parameter settings are stored in the \link[S4Vectors]{metadata} |
56 | 57 |
#' \code{"celda_parameters"} slot. Column \code{celda_feature_module} in |
... | ... |
@@ -763,7 +763,7 @@ setMethod("celda_G", |
763 | 763 |
cellIx <- sample(seq(ncol(counts)), maxCells) |
764 | 764 |
} |
765 | 765 |
|
766 |
- fm <- .factorizeMatrixCelda_G(x = sce, useAssay = useAssay, type = "counts") |
|
766 |
+ fm <- .factorizeMatrixCelda_G(sce, useAssay = useAssay, type = "counts") |
|
767 | 767 |
|
768 | 768 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
769 | 769 |
if (!is.null(modules)) { |
... | ... |
@@ -1,13 +1,19 @@ |
1 | 1 |
#' @title Feature clustering with Celda |
2 | 2 |
#' @description Clusters the rows of a count matrix containing single-cell data |
3 |
-#' into L modules. |
|
3 |
+#' into L modules. The |
|
4 |
+#' \code{useAssay} \link[SummarizedExperiment]{assay} slot in |
|
5 |
+#' \code{altExpName} \link[SingleCellExperiment]{altExp} slot will be used if |
|
6 |
+#' it exists. Otherwise, the \code{useAssay} |
|
7 |
+#' \link[SummarizedExperiment]{assay} slot in \code{x} will be used if |
|
8 |
+#' \code{x} is a \linkS4class{SingleCellExperiment} object. |
|
4 | 9 |
#' @param x A numeric \link{matrix} of counts or a |
5 | 10 |
#' \linkS4class{SingleCellExperiment} |
6 | 11 |
#' with the matrix located in the assay slot under \code{useAssay}. |
7 | 12 |
#' Rows represent features and columns represent cells. |
8 |
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
|
9 |
-#' slot to use if \code{x} is a |
|
10 |
-#' \linkS4class{SingleCellExperiment} object. Default "counts". |
|
13 |
+#' @param useAssay A string specifying the name of the |
|
14 |
+#' \link[SummarizedExperiment]{assay} slot to use. Default "counts". |
|
15 |
+#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot |
|
16 |
+#' to use. Default "featureSubset". |
|
11 | 17 |
#' @param L Integer. Number of feature modules. |
12 | 18 |
#' @param beta Numeric. Concentration parameter for Phi. Adds a pseudocount to |
13 | 19 |
#' each feature module in each cell. Default 1. |
... | ... |
@@ -66,6 +72,7 @@ setMethod("celda_G", |
66 | 72 |
signature(x = "SingleCellExperiment"), |
67 | 73 |
function(x, |
68 | 74 |
useAssay = "counts", |
75 |
+ altExpName = "featureSubset", |
|
69 | 76 |
L, |
70 | 77 |
beta = 1, |
71 | 78 |
delta = 1, |
... | ... |
@@ -83,12 +90,24 @@ setMethod("celda_G", |
83 | 90 |
verbose = TRUE) { |
84 | 91 |
|
85 | 92 |
xClass <- "SingleCellExperiment" |
86 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
87 | 93 |
|
88 |
- sce <- .celdaGWithSeed(counts = counts, |
|
94 |
+ if (!altExpName %in% SingleCellExperiment::altExpNames(x)) { |
|
95 |
+ stop(altExpName, " not in 'altExpNames(x)'. Run ", |
|
96 |
+ "selectFeatures(x) first!") |
|
97 |
+ } |
|
98 |
+ |
|
99 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
100 |
+ |
|
101 |
+ if (!useAssay %in% SummarizedExperiment::assayNames(altExp)) { |
|
102 |
+ stop(useAssay, " not in assayNames(altExp(x, altExpName))") |
|
103 |
+ } |
|
104 |
+ |
|
105 |
+ counts <- SummarizedExperiment::assay(altExp, i = useAssay) |
|
106 |
+ |
|
107 |
+ altExp <- .celdaGWithSeed(counts = counts, |
|
89 | 108 |
xClass = xClass, |
90 | 109 |
useAssay = useAssay, |
91 |
- sce = x, |
|
110 |
+ sce = altExp, |
|
92 | 111 |
L = L, |
93 | 112 |
beta = beta, |
94 | 113 |
delta = delta, |
... | ... |
@@ -104,7 +123,8 @@ setMethod("celda_G", |
104 | 123 |
yInit = yInit, |
105 | 124 |
logfile = logfile, |
106 | 125 |
verbose = verbose) |
107 |
- return(sce) |
|
126 |
+ SingleCellExperiment::altExp(x, altExpName) <- altExp |
|
127 |
+ return(x) |
|
108 | 128 |
} |
109 | 129 |
) |
110 | 130 |
|
... | ... |
@@ -114,6 +134,8 @@ setMethod("celda_G", |
114 | 134 |
setMethod("celda_G", |
115 | 135 |
signature(x = "matrix"), |
116 | 136 |
function(x, |
137 |
+ useAssay = "counts", |
|
138 |
+ altExpName = "featureSubset", |
|
117 | 139 |
L, |
118 | 140 |
beta = 1, |
119 | 141 |
delta = 1, |
... | ... |
@@ -130,14 +152,16 @@ setMethod("celda_G", |
130 | 152 |
logfile = NULL, |
131 | 153 |
verbose = TRUE) { |
132 | 154 |
|
155 |
+ ls <- list() |
|
156 |
+ ls[[useAssay]] <- x |
|
157 |
+ sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
|
158 |
+ SingleCellExperiment::altExp(sce, altExpName) <- sce |
|
133 | 159 |
xClass <- "matrix" |
134 |
- useAssay <- NULL |
|
135 |
- sce <- SingleCellExperiment::SingleCellExperiment( |
|
136 |
- assays = list(counts = x)) |
|
137 |
- sce <- .celdaGWithSeed(counts = x, |
|
160 |
+ |
|
161 |
+ altExp <- .celdaGWithSeed(counts = x, |
|
138 | 162 |
xClass = xClass, |
139 | 163 |
useAssay = useAssay, |
140 |
- sce = sce, |
|
164 |
+ sce = SingleCellExperiment::altExp(sce, altExpName), |
|
141 | 165 |
L = L, |
142 | 166 |
beta = beta, |
143 | 167 |
delta = delta, |
... | ... |
@@ -153,6 +177,7 @@ setMethod("celda_G", |
153 | 177 |
yInit = yInit, |
154 | 178 |
logfile = logfile, |
155 | 179 |
verbose = verbose) |
180 |
+ SingleCellExperiment::altExp(sce, altExpName) <- altExp |
|
156 | 181 |
return(sce) |
157 | 182 |
} |
158 | 183 |
) |
... | ... |
@@ -738,7 +763,7 @@ setMethod("celda_G", |
738 | 763 |
cellIx <- sample(seq(ncol(counts)), maxCells) |
739 | 764 |
} |
740 | 765 |
|
741 |
- fm <- factorizeMatrix(x = sce, useAssay = useAssay, type = "counts") |
|
766 |
+ fm <- .factorizeMatrixCelda_G(x = sce, useAssay = useAssay, type = "counts") |
|
742 | 767 |
|
743 | 768 |
modulesToUse <- seq(nrow(fm$counts$cell)) |
744 | 769 |
if (!is.null(modules)) { |
... | ... |
@@ -723,7 +723,10 @@ setMethod("celda_G", |
723 | 723 |
useAssay, |
724 | 724 |
maxCells, |
725 | 725 |
minClusterSize, |
726 |
- modules) { |
|
726 |
+ modules, |
|
727 |
+ normalize, |
|
728 |
+ scaleFactor, |
|
729 |
+ transformationFun) { |
|
727 | 730 |
|
728 | 731 |
counts <- SummarizedExperiment::assay(sce, i = useAssay) |
729 | 732 |
counts <- .processCounts(counts) |
... | ... |
@@ -750,9 +753,9 @@ setMethod("celda_G", |
750 | 753 |
} |
751 | 754 |
|
752 | 755 |
norm <- t(normalizeCounts(fm$counts$cell[modulesToUse, cellIx], |
753 |
- normalize = "proportion", |
|
754 |
- transformationFun = sqrt |
|
755 |
- )) |
|
756 |
+ normalize = normalize, |
|
757 |
+ scaleFactor = scaleFactor, |
|
758 |
+ transformationFun = transformationFun)) |
|
756 | 759 |
return(list(norm = norm, cellIx = cellIx)) |
757 | 760 |
} |
758 | 761 |
|
... | ... |
@@ -7,7 +7,7 @@ |
7 | 7 |
#' Rows represent features and columns represent cells. |
8 | 8 |
#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay} |
9 | 9 |
#' slot to use if \code{x} is a |
10 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts". |
|
10 |
+#' \linkS4class{SingleCellExperiment} object. Default "counts". |
|
11 | 11 |
#' @param L Integer. Number of feature modules. |
12 | 12 |
#' @param beta Numeric. Concentration parameter for Phi. Adds a pseudocount to |
13 | 13 |
#' each feature module in each cell. Default 1. |
... | ... |
@@ -45,8 +45,10 @@ |
45 | 45 |
#' @param logfile Character. Messages will be redirected to a file named |
46 | 46 |
#' `logfile`. If NULL, messages will be printed to stdout. Default NULL. |
47 | 47 |
#' @param verbose Logical. Whether to print log messages. Default TRUE. |
48 |
-#' @return An object of class `celda_G` with the feature module clusters stored |
|
49 |
-#' in `y`. |
|
48 |
+#' @return A \linkS4class{SingleCellExperiment} object. Function |
|
49 |
+#' parameter settings are stored in the \link[S4Vectors]{metadata} |
|
50 |
+#' \code{"celda_parameters"} slot. Column \code{celda_feature_module} in |
|
51 |
+#' \link[SummarizedExperiment]{rowData} contains feature modules. |
|
50 | 52 |
#' @seealso \link{celda_C} for cell clustering and \link{celda_CG} for |
51 | 53 |
#' simultaneous clustering of features and cells. \link{celdaGridSearch} can |
52 | 54 |
#' be used to run multiple values of L and multiple chains in parallel. |
... | ... |
@@ -54,7 +54,8 @@ |
54 | 54 |
#' data(celdaGSim) |
55 | 55 |
#' sce <- celda_G(celdaGSim$counts, L = celdaGSim$L, nchains = 1) |
56 | 56 |
#' @export |
57 |
-setGeneric("celda_G", function(x, ...) {standardGeneric("celda_G")}) |
|
57 |
+setGeneric("celda_G", function(x, ...) { |
|
58 |
+ standardGeneric("celda_G")}) |
|
58 | 59 |
|
59 | 60 |
|
60 | 61 |
#' @rdname celda_G |
... | ... |
@@ -799,4 +800,3 @@ setMethod("celda_G", |
799 | 800 |
|
800 | 801 |
return(sce) |
801 | 802 |
} |
802 |
- |
... | ... |
@@ -497,7 +497,7 @@ setMethod("celda_G", |
497 | 497 |
} |
498 | 498 |
|
499 | 499 |
bestResult <- methods::new("celda_G", |
500 |
- celdaClusters = list(y = yBest), |
|
500 |
+ clusters = list(y = yBest), |
|
501 | 501 |
params = list( |
502 | 502 |
L = as.integer(L), |
503 | 503 |
beta = beta, |
... | ... |
@@ -703,10 +703,10 @@ setMethod("celda_G", |
703 | 703 |
|
704 | 704 |
|
705 | 705 |
.reorderCeldaG <- function(counts, res) { |
706 |
- if (params(res)$L > 2 & isTRUE(length(unique(res@celdaClusters$y)) > 1)) { |
|
707 |
- res@celdaClusters$y <- as.integer(as.factor(res@celdaClusters$y)) |
|
706 |
+ if (params(res)$L > 2 & isTRUE(length(unique(celdaClusters(res)$y)) > 1)) { |
|
707 |
+ res@clusters$y <- as.integer(as.factor(celdaClusters(res)$y)) |
|
708 | 708 |
fm <- factorizeMatrix(counts, res) |
709 |
- uniqueY <- sort(unique(res@celdaClusters$y)) |
|
709 |
+ uniqueY <- sort(unique(celdaClusters(res)$y)) |
|
710 | 710 |
cs <- prop.table(t(fm$posterior$cell[uniqueY, ]), 2) |
711 | 711 |
d <- .cosineDist(cs) |
712 | 712 |
h <- stats::hclust(d, method = "complete") |
... | ... |
@@ -789,13 +789,13 @@ setMethod("celda_G", |
789 | 789 |
verbose = verbose, |
790 | 790 |
completeLogLik = celdaGMod@completeLogLik, |
791 | 791 |
finalLogLik = celdaGMod@finalLogLik, |
792 |
- featureModuleLevels = sort(unique(celdaGMod@celdaClusters$y))) |
|
792 |
+ featureModuleLevels = sort(unique(celdaClusters(celdaGMod)$y))) |
|
793 | 793 |
|
794 | 794 |
SummarizedExperiment::rowData(sce)["rownames"] <- celdaGMod@names$row |
795 | 795 |
SummarizedExperiment::colData(sce)["colnames"] <- |
796 | 796 |
celdaGMod@names$column |
797 | 797 |
SummarizedExperiment::rowData(sce)["celda_feature_module"] <- |
798 |
- celdaGMod@celdaClusters$y |
|
798 |
+ celdaClusters(celdaGMod)$y |
|
799 | 799 |
|
800 | 800 |
return(sce) |
801 | 801 |
} |
... | ... |
@@ -613,90 +613,6 @@ setMethod("celda_G", |
613 | 613 |
} |
614 | 614 |
|
615 | 615 |
|
616 |
-.factorizeMatrixCelda_G <- function(sce, useAssay, type) { |
|
617 |
- counts <- SummarizedExperiment::assay(sce, i = useAssay) |
|
618 |
- counts <- .processCounts(counts) |
|
619 |
- # compareCountMatrix(counts, celdaMod) |
|
620 |
- |
|
621 |
- L <- S4Vectors::metadata(sce)$celda_parameters$L |
|
622 |
- y <- celdaModules(sce) |
|
623 |
- beta <- S4Vectors::metadata(sce)$celda_parameters$beta |
|
624 |
- delta <- S4Vectors::metadata(sce)$celda_parameters$delta |
|
625 |
- gamma <- S4Vectors::metadata(sce)$celda_parameters$gamma |
|
626 |
- |
|
627 |
- p <- .cGDecomposeCounts(counts = counts, y = y, L = L) |
|
628 |
- nTSByC <- p$nTSByC |
|
629 |
- nByG <- p$nByG |
|
630 |
- nByTS <- p$nByTS |
|
631 |
- nGByTS <- p$nGByTS |
|
632 |
- nM <- p$nM |
|
633 |
- nG <- p$nG |
|
634 |
- rm(p) |
|
635 |
- |
|
636 |
- nGByTS[nGByTS == 0] <- 1 |
|
637 |
- nGByTS <- matrix(0, nrow = length(y), ncol = L) |
|
638 |
- nGByTS[cbind(seq(nG), y)] <- nByG |
|
639 |
- |
|
640 |
- LNames <- paste0("L", seq(L)) |
|
641 |
- colnames(nTSByC) <- colnames(sce) |
|
642 |
- rownames(nTSByC) <- LNames |
|
643 |
- colnames(nGByTS) <- LNames |
|
644 |
- rownames(nGByTS) <- rownames(sce) |
|
645 |
- names(nGByTS) <- LNames |
|
646 |
- |
|
647 |
- countsList <- c() |
|
648 |
- propList <- c() |
|
649 |
- postList <- c() |
|
650 |
- res <- list() |
|
651 |
- |
|
652 |
- if (any("counts" %in% type)) { |
|
653 |
- countsList <- list( |
|
654 |
- cell = nTSByC, |
|
655 |
- module = nGByTS, |
|
656 |
- geneDistribution = nGByTS |
|
657 |
- ) |
|
658 |
- res <- c(res, list(counts = countsList)) |
|
659 |
- } |
|
660 |
- |
|
661 |
- if (any("proportion" %in% type)) { |
|
662 |
- ## Need to avoid normalizing cell/gene states with zero cells/genes |
|
663 |
- uniqueY <- sort(unique(y)) |
|
664 |
- tempNGByTS <- nGByTS |
|
665 |
- tempNGByTS[, uniqueY] <- normalizeCounts(tempNGByTS[, uniqueY], |
|
666 |
- normalize = "proportion" |
|
667 |
- ) |
|
668 |
- tempNGByTS <- nGByTS / sum(nGByTS) |
|
669 |
- |
|
670 |
- propList <- list( |
|
671 |
- cell = normalizeCounts(nTSByC, |
|
672 |
- normalize = "proportion" |
|
673 |
- ), |
|
674 |
- module = tempNGByTS, |
|
675 |
- geneDistribution = tempNGByTS |
|
676 |
- ) |
|
677 |
- res <- c(res, list(proportions = propList)) |
|
678 |
- } |
|
679 |
- |
|
680 |
- if (any("posterior" %in% type)) { |
|
681 |
- gs <- nGByTS |
|
682 |
- gs[cbind(seq(nG), y)] <- gs[cbind(seq(nG), y)] + delta |
|
683 |
- gs <- normalizeCounts(gs, normalize = "proportion") |
|
684 |
- tempNGByTS <- (nGByTS + gamma) / sum(nGByTS + gamma) |
|
685 |
- |
|
686 |
- postList <- list( |
|
687 |
- cell = normalizeCounts(nTSByC + beta, |
|
688 |
- normalize = "proportion" |
|
689 |
- ), |
|
690 |
- module = gs, |
|
691 |
- geneDistribution = tempNGByTS |
|
692 |
- ) |
|
693 |
- res <- c(res, posterior = list(postList)) |
|
694 |
- } |
|
695 |
- |
|
696 |
- return(res) |
|
697 |
-} |
|
698 |
- |
|
699 |
- |
|
700 | 616 |
# Calculate log-likelihood of celda_CG model |
701 | 617 |
.cGCalcLL <- function(nTSByC, |
702 | 618 |
nByTS, |
... | ... |
@@ -739,29 +655,6 @@ setMethod("celda_G", |
739 | 655 |
} |
740 | 656 |
|
741 | 657 |
|
742 |
-.logLikelihoodcelda_G <- function(counts, y, L, beta, delta, gamma) { |
|
743 |
- if (sum(y > L) > 0) { |
|
744 |
- stop("Assigned value of feature module greater than the total number", |
|
745 |
- " of feature modules!") |
|
746 |
- } |
|
747 |
- p <- .cGDecomposeCounts(counts = counts, y = y, L = L) |
|
748 |
- final <- .cGCalcLL( |
|
749 |
- nTSByC = p$nTSByC, |
|
750 |
- nByTS = p$nByTS, |
|
751 |
- nByG = p$nByG, |
|
752 |
- nGByTS = p$nGByTS, |
|
753 |
- nM = p$nM, |
|
754 |
- nG = p$nG, |
|
755 |
- L = L, |
|
756 |
- beta = beta, |
|
757 |
- delta = delta, |
|
758 |
- gamma = gamma |
|
759 |
- ) |
|
760 |
- |
|
761 |
- return(final) |
|
762 |
-} |
|
763 |
- |
|
764 |
- |
|
765 | 658 |
# Takes raw counts matrix and converts it to a series of matrices needed for |
766 | 659 |
# log likelihood calculation |
767 | 660 |
# @param counts Integer matrix. Rows represent features and columns represent |
... | ... |
@@ -809,43 +702,6 @@ setMethod("celda_G", |
809 | 702 |
} |
810 | 703 |
|
811 | 704 |