Browse code

celdaUmap functionality for celda_G, celda_C

Sean Corbett authored on 17/01/2019 18:40:16
Showing 12 changed files

... ...
@@ -10,6 +10,7 @@ export(celdaHeatmap)
10 10
 export(celdaPerplexity)
11 11
 export(celdaProbabilityMap)
12 12
 export(celdaTsne)
13
+export(celdaUmap)
13 14
 export(celda_C)
14 15
 export(celda_CG)
15 16
 export(celda_G)
... ...
@@ -59,6 +60,7 @@ export(violinPlot)
59 60
 exportMethods(celdaHeatmap)
60 61
 exportMethods(celdaProbabilityMap)
61 62
 exportMethods(celdaTsne)
63
+exportMethods(celdaUmap)
62 64
 exportMethods(clusterProbability)
63 65
 exportMethods(factorizeMatrix)
64 66
 exportMethods(featureModuleLookup)
... ...
@@ -617,55 +617,94 @@ setMethod("celdaTsne",
617 617
                      initial.dims=20, modules=NULL, perplexity=20, max.iter=2500, 
618 618
                      seed=12345, ...) {
619 619
 
620
-            counts = processCounts(counts)
621
-            compareCountMatrix(counts, celda.mod)
622
-            
623
-            ## Checking if max.cells and min.cluster.size will work
624
-            if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@params$K)) {
625
-              stop(paste0("Cannot distribute ", max.cells, " cells among ", 
626
-                          celda.mod@params$K, " clusters while maintaining a minumum of ", 
627
-                          min.cluster.size, 
628
-                          " cells per cluster. Try increasing 'max.cells' or decreasing 'min.cluster.size'."))
629
-            }
620
+
621
+            prepared.count.info = prepareCountsForDimReduction.celda_C(counts, celda.mod, max.cells,
622
+                                                                       min.cluster.size, modules)
630 623
             
631
-            ## Select a subset of cells to sample if greater than 'max.cells'
632
-            total.cells.to.remove = ncol(counts) - max.cells
633
-            z.include = rep(TRUE, ncol(counts))
634
-            if(total.cells.to.remove > 0) {
635
-          	z.ta = tabulate(celda.mod@clusters$z, celda.mod@params$K)
636
-          	
637
-          	## Number of cells that can be sampled from each cluster without 
638
-          	## going below the minimum threshold
639
-          	cluster.cells.to.sample = z.ta - min.cluster.size          
640
-          	cluster.cells.to.sample[cluster.cells.to.sample < 0] = 0
641
-          	
642
-          	## Number of cells to sample after exluding smaller clusters
643
-          	## Rounding can cause number to be off by a few, so ceiling is 
644
-          	## used with a second round of subtraction
645
-          	cluster.n.to.sample = ceiling((cluster.cells.to.sample / sum(cluster.cells.to.sample)) * total.cells.to.remove)
646
-          	diff = sum(cluster.n.to.sample) - total.cells.to.remove 
647
-          	cluster.n.to.sample[which.max(cluster.n.to.sample)] = cluster.n.to.sample[which.max(cluster.n.to.sample)] - diff
648
-          
649
-          	## Perform sampling for each cluster
650
-          	for(i in which(cluster.n.to.sample > 0)) {
651
-          	  z.include[sample(which(celda.mod@clusters$z == i), cluster.n.to.sample[i])] = FALSE
652
-          	}
653
-            }   
654
-            cell.ix = which(z.include)
655
-          
656
-            norm = t(normalizeCounts(counts[,cell.ix], normalize="proportion", 
657
-                                     transformation.fun=sqrt))
658
-            res = calculateTsne(norm, perplexity=perplexity, max.iter=max.iter, 
659
-                                seed=seed, do.pca=TRUE, 
660
-                                initial.dims = initial.dims)
624
+            res = calculateTsne(prepared.count.info$norm, perplexity=perplexity, max.iter=max.iter, 
625
+                                seed=seed, do.pca=TRUE, initial.dims = initial.dims)
661 626
             final = matrix(NA, nrow=ncol(counts), ncol=2)
662
-            final[cell.ix,] = res
627
+            final[prepared.couunt.info$cell.ix,] = res
663 628
             rownames(final) = colnames(counts)
664 629
             colnames(final) = c("tsne_1", "tsne_2")
665 630
             return(final)
666 631
           })
667 632
 
668 633
 
634
+#' @title umap for celda_C
635
+#' @description Embeds cells in two dimensions using umap based on a `celda_C` model. PCA on the normalized counts is used to reduce the number of features before applying umap. 
636
+#' 
637
+#' @param counts Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.
638
+#' @param celda.mod Celda object of class `celda_C`. 
639
+#' @param max.cells Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.
640
+#' @param min.cluster.size Integer. Do not subsample cell clusters below this threshold. Default 100. 
641
+#' @param initial.dims Integer. PCA will be used to reduce the dimentionality of the dataset. The top 'initial.dims' principal components will be used for tSNE. Default 20.
642
+#' @param perplexity Numeric. Perplexity parameter for tSNE. Default 20.
643
+#' @param max.iter Integer. Maximum number of iterations in tSNE generation. Default 2500.
644
+#' @param seed Integer. Passed to `set.seed()`. Default 12345. If NULL, no calls to `set.seed()` are made.
645
+#' @param ... Additional parameters.
646
+#' @seealso `celda_C()` for clustering cells and `celdaHeatmap()` for displaying expression
647
+#' @examples
648
+#' umap.res = celdaUmap(celda.C.sim$counts, celda.C.mod)
649
+#' @return A two column matrix of t-SNE coordinates
650
+#' @export
651
+setMethod("celdaUmap",
652
+          signature(celda.mod = "celda_C"),
653
+          function(counts, celda.mod, max.cells=25000, min.cluster.size=100,
654
+                   modules=NULL, umap.config=umap::umap.defaults) {
655
+            prepared.count.info = prepareCountsForDimReduction.celda_C(counts, celda.mod, max.cells,
656
+                                                                       min.cluster.size, modules)
657
+            res = calculateUmap(prepared.count.info$norm, umap.config)
658
+            final = matrix(NA, nrow=ncol(counts), ncol=2)
659
+            final[prepared.count.info$cell.ix,] = res
660
+            rownames(final) = colnames(counts)
661
+            colnames(final) = c("umap_1", "umap_2")
662
+            return(final)
663
+          })
664
+
665
+
666
+prepareCountsForDimReduction.celda_C = function(counts, celda.mod, max.cells=25000, min.cluster.size=100,
667
+                                                modules=NULL) {
668
+  counts = processCounts(counts)
669
+  compareCountMatrix(counts, celda.mod)
670
+  
671
+  ## Checking if max.cells and min.cluster.size will work
672
+  if((max.cells < ncol(counts)) & (max.cells / min.cluster.size < celda.mod@params$K)) {
673
+  stop(paste0("Cannot distribute ", max.cells, " cells among ", 
674
+              celda.mod@params$K, " clusters while maintaining a minumum of ", 
675
+              min.cluster.size, 
676
+              " cells per cluster. Try increasing 'max.cells' or decreasing 'min.cluster.size'."))
677
+  }
678
+  
679
+  ## Select a subset of cells to sample if greater than 'max.cells'
680
+  total.cells.to.remove = ncol(counts) - max.cells
681
+  z.include = rep(TRUE, ncol(counts))
682
+  if(total.cells.to.remove > 0) {
683
+    z.ta = tabulate(celda.mod@clusters$z, celda.mod@params$K)
684
+    
685
+    ## Number of cells that can be sampled from each cluster without 
686
+    ## going below the minimum threshold
687
+    cluster.cells.to.sample = z.ta - min.cluster.size          
688
+    cluster.cells.to.sample[cluster.cells.to.sample < 0] = 0
689
+    
690
+    ## Number of cells to sample after exluding smaller clusters
691
+    ## Rounding can cause number to be off by a few, so ceiling is 
692
+    ## used with a second round of subtraction
693
+    cluster.n.to.sample = ceiling((cluster.cells.to.sample / sum(cluster.cells.to.sample)) * total.cells.to.remove)
694
+    diff = sum(cluster.n.to.sample) - total.cells.to.remove 
695
+    cluster.n.to.sample[which.max(cluster.n.to.sample)] = cluster.n.to.sample[which.max(cluster.n.to.sample)] - diff
696
+    
697
+    ## Perform sampling for each cluster
698
+    for(i in which(cluster.n.to.sample > 0)) {
699
+      z.include[sample(which(celda.mod@clusters$z == i), cluster.n.to.sample[i])] = FALSE
700
+    }
701
+  }   
702
+  cell.ix = which(z.include)
703
+  norm = t(normalizeCounts(counts[,cell.ix], normalize="proportion", 
704
+                         transformation.fun=sqrt))
705
+  return(list(norm=norm, cell.ix=cell.ix))
706
+}
707
+
669 708
 
670 709
 #' @title Probability map for a celda_C model
671 710
 #' @description Renders probability and relative expression heatmaps to visualize the relationship between cell populations and samples.
... ...
@@ -763,7 +763,7 @@ setMethod("celdaTsne",
763 763
 #' @param umap.config Object of class `umap.config`. Configures parameters for umap. Default `umap::umap.defaults`
764 764
 #' @seealso `celda_CG()` for clustering features and cells  and `celdaHeatmap()` for displaying expression
765 765
 #' @examples
766
-#' tsne.res = celdaTsne(celda.CG.sim$counts, celda.CG.mod)
766
+#' umap.res = celdaUmap(celda.CG.sim$counts, celda.CG.mod)
767 767
 #' @return A two column matrix of t-SNE coordinates
768 768
 #' @export
769 769
 setMethod("celdaUmap",
... ...
@@ -603,27 +603,9 @@ setMethod("celdaTsne",
603 603
                     initial.dims=20, modules=NULL, perplexity=20, max.iter=2500, 
604 604
                     seed=12345, ...) {
605 605
   
606
-            if(max.cells > ncol(counts)) {
607
-              max.cells = ncol(counts)
608
-            }
609 606
             
610
-            fm = factorizeMatrix(counts=counts, celda.mod=celda.mod, 
611
-                                 type="counts")
612
-              
613
-            modules.to.use = 1:nrow(fm$counts$cell)
614
-            if (!is.null(modules)) {
615
-          	if (!all(modules %in% modules.to.use)) {
616
-          	  stop("'modules' must be a vector of numbers between 1 and ", 
617
-          	       modules.to.use, ".")
618
-          	}
619
-          	modules.to.use = modules 
620
-            }
621
-             
622
-            cell.ix = sample(1:ncol(counts), max.cells)
623
-            norm = t(normalizeCounts(fm$counts$cell[modules.to.use,cell.ix], 
624
-                                     normalize="proportion", 
625
-                                     transformation.fun=sqrt))
626
-          
607
+            norm = prepareCountsForDimReduction.celda_G(counts, celda.mod, max.cells, 
608
+                                                        min.cluster.size, modules) 
627 609
             res = calculateTsne(norm, do.pca=FALSE, perplexity=perplexity, 
628 610
                                 max.iter=max.iter, seed=seed)
629 611
             rownames(res) = colnames(counts)
... ...
@@ -632,6 +614,62 @@ setMethod("celdaTsne",
632 614
           })
633 615
 
634 616
 
617
+#' @title umap for celda_G
618
+#' @description Embeds cells in two dimensions using umap based on a `celda_G` model. umap is run on module probabilities to reduce the number of features instead of using PCA. Module probabilities square-root trasformed before applying tSNE. 
619
+#' 
620
+#' @param counts Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.
621
+#' @param celda.mod Celda object of class `celda_CG`. 
622
+#' @param max.cells Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.
623
+#' @param min.cluster.size Integer. Do not subsample cell clusters below this threshold. Default 100. 
624
+#' @param modules Integer vector. Determines which features modules to use for tSNE. If NULL, all modules will be used. Default NULL.
625
+#' @param umap.config Object of class `umap.config`. Configures parameters for umap. Default `umap::umap.defaults`
626
+#' @seealso `celda_G()` for clustering features and cells  and `celdaHeatmap()` for displaying expression
627
+#' @examples
628
+#' umap.res = celdaUmap(celda.G.sim$counts, celda.G.mod)
629
+#' @return A two column matrix of t-SNE coordinates
630
+#' @export
631
+setMethod("celdaUmap",
632
+          signature(celda.mod = "celda_G"),
633
+          function(counts, celda.mod, max.cells=25000, min.cluster.size=100,
634
+                   modules=NULL, umap.config=umap::umap.defaults) {
635
+            prepared.count.info = prepareCountsForDimReduction.celda_G(counts, celda.mod,
636
+                                                                       max.cells, min.cluster.size,
637
+                                                                       modules)
638
+            umap.res = calculateUmap(prepared.count.info$norm, umap.config)
639
+            final = matrix(NA, nrow=ncol(counts), ncol=2)
640
+            final[prepared.count.info$cell.ix, ] = umap.res
641
+            rownames(final) = colnames(counts)
642
+            colnames(final) = c("umap_1", "umap_2")
643
+            return(final)
644
+          })
645
+
646
+
647
+prepareCountsForDimReduction.celda_G = function(counts, celda.mod, max.cells=25000, min.cluster.size=100,
648
+                                                modules=NULL) {
649
+  if(max.cells > ncol(counts)) {
650
+              max.cells = ncol(counts)
651
+            }
652
+            
653
+  fm = factorizeMatrix(counts=counts, celda.mod=celda.mod, 
654
+                       type="counts")
655
+    
656
+  modules.to.use = 1:nrow(fm$counts$cell)
657
+  if (!is.null(modules)) {
658
+  if (!all(modules %in% modules.to.use)) {
659
+    stop("'modules' must be a vector of numbers between 1 and ", 
660
+         modules.to.use, ".")
661
+  }
662
+  modules.to.use = modules 
663
+  }
664
+   
665
+  cell.ix = sample(1:ncol(counts), max.cells)
666
+  norm = t(normalizeCounts(fm$counts$cell[modules.to.use,cell.ix], 
667
+                           normalize="proportion", 
668
+                           transformation.fun=sqrt))
669
+  return(list(norm=norm, cell.ix=cell.ix))
670
+}
671
+
672
+
635 673
 #' @title Lookup the module of a feature
636 674
 #' @description Finds the module assignments of given features in a `celda_G()` model
637 675
 #'  
... ...
@@ -11,7 +11,21 @@ celdaTsne(counts, celda.mod, max.cells = 25000, min.cluster.size = 100,
11 11
 \arguments{
12 12
 \item{counts}{Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.}
13 13
 
14
-\item{celda.mod}{Celda model. Options available in `celda::available.models`.}
14
+\item{celda.mod}{Celda object of class `celda_CG`.}
15
+
16
+\item{max.cells}{Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.}
17
+
18
+\item{min.cluster.size}{Integer. Do not subsample cell clusters below this threshold. Default 100.}
19
+
20
+\item{modules}{Integer vector. Determines which features modules to use for tSNE. If NULL, all modules will be used. Default NULL.}
21
+
22
+\item{perplexity}{Numeric. Perplexity parameter for tSNE. Default 20.}
23
+
24
+\item{max.iter}{Integer. Maximum number of iterations in tSNE generation. Default 2500.}
25
+
26
+\item{seed}{Integer. Passed to `set.seed()`. Default 12345. If NULL, no calls to `set.seed()` are made.}
27
+
28
+\item{...}{Additional parameters.}
15 29
 
16 30
 \item{...}{Additional parameters.}
17 31
 }
18 32
new file mode 100755
... ...
@@ -0,0 +1,42 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/celda_C.R
3
+\docType{methods}
4
+\name{celdaUmap,celda_C-method}
5
+\alias{celdaUmap,celda_C-method}
6
+\title{umap for celda_C}
7
+\usage{
8
+\S4method{celdaUmap}{celda_C}(counts, celda.mod, max.cells = 25000,
9
+  min.cluster.size = 100, modules = NULL,
10
+  umap.config = umap::umap.defaults)
11
+}
12
+\arguments{
13
+\item{counts}{Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.}
14
+
15
+\item{celda.mod}{Celda object of class `celda_C`.}
16
+
17
+\item{max.cells}{Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.}
18
+
19
+\item{min.cluster.size}{Integer. Do not subsample cell clusters below this threshold. Default 100.}
20
+
21
+\item{initial.dims}{Integer. PCA will be used to reduce the dimentionality of the dataset. The top 'initial.dims' principal components will be used for tSNE. Default 20.}
22
+
23
+\item{perplexity}{Numeric. Perplexity parameter for tSNE. Default 20.}
24
+
25
+\item{max.iter}{Integer. Maximum number of iterations in tSNE generation. Default 2500.}
26
+
27
+\item{seed}{Integer. Passed to `set.seed()`. Default 12345. If NULL, no calls to `set.seed()` are made.}
28
+
29
+\item{...}{Additional parameters.}
30
+}
31
+\value{
32
+A two column matrix of t-SNE coordinates
33
+}
34
+\description{
35
+Embeds cells in two dimensions using umap based on a `celda_C` model. PCA on the normalized counts is used to reduce the number of features before applying umap.
36
+}
37
+\examples{
38
+umap.res = celdaUmap(celda.C.sim$counts, celda.C.mod)
39
+}
40
+\seealso{
41
+`celda_C()` for clustering cells and `celdaHeatmap()` for displaying expression
42
+}
0 43
new file mode 100755
... ...
@@ -0,0 +1,36 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/celda_CG.R
3
+\docType{methods}
4
+\name{celdaUmap,celda_CG-method}
5
+\alias{celdaUmap,celda_CG-method}
6
+\title{umap for celda_CG}
7
+\usage{
8
+\S4method{celdaUmap}{celda_CG}(counts, celda.mod, max.cells = 25000,
9
+  min.cluster.size = 100, modules = NULL,
10
+  umap.config = umap::umap.defaults)
11
+}
12
+\arguments{
13
+\item{counts}{Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.}
14
+
15
+\item{celda.mod}{Celda object of class `celda_CG`.}
16
+
17
+\item{max.cells}{Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.}
18
+
19
+\item{min.cluster.size}{Integer. Do not subsample cell clusters below this threshold. Default 100.}
20
+
21
+\item{modules}{Integer vector. Determines which features modules to use for tSNE. If NULL, all modules will be used. Default NULL.}
22
+
23
+\item{umap.config}{Object of class `umap.config`. Configures parameters for umap. Default `umap::umap.defaults`}
24
+}
25
+\value{
26
+A two column matrix of t-SNE coordinates
27
+}
28
+\description{
29
+Embeds cells in two dimensions using umap based on a `celda_CG` model. umap is run on module probabilities to reduce the number of features instead of using PCA. Module probabilities square-root trasformed before applying tSNE.
30
+}
31
+\examples{
32
+umap.res = celdaUmap(celda.CG.sim$counts, celda.CG.mod)
33
+}
34
+\seealso{
35
+`celda_CG()` for clustering features and cells  and `celdaHeatmap()` for displaying expression
36
+}
0 37
new file mode 100755
... ...
@@ -0,0 +1,36 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/celda_G.R
3
+\docType{methods}
4
+\name{celdaUmap,celda_G-method}
5
+\alias{celdaUmap,celda_G-method}
6
+\title{umap for celda_G}
7
+\usage{
8
+\S4method{celdaUmap}{celda_G}(counts, celda.mod, max.cells = 25000,
9
+  min.cluster.size = 100, modules = NULL,
10
+  umap.config = umap::umap.defaults)
11
+}
12
+\arguments{
13
+\item{counts}{Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.}
14
+
15
+\item{celda.mod}{Celda object of class `celda_CG`.}
16
+
17
+\item{max.cells}{Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.}
18
+
19
+\item{min.cluster.size}{Integer. Do not subsample cell clusters below this threshold. Default 100.}
20
+
21
+\item{modules}{Integer vector. Determines which features modules to use for tSNE. If NULL, all modules will be used. Default NULL.}
22
+
23
+\item{umap.config}{Object of class `umap.config`. Configures parameters for umap. Default `umap::umap.defaults`}
24
+}
25
+\value{
26
+A two column matrix of t-SNE coordinates
27
+}
28
+\description{
29
+Embeds cells in two dimensions using umap based on a `celda_G` model. umap is run on module probabilities to reduce the number of features instead of using PCA. Module probabilities square-root trasformed before applying tSNE.
30
+}
31
+\examples{
32
+umap.res = celdaUmap(celda.G.sim$counts, celda.G.mod)
33
+}
34
+\seealso{
35
+`celda_G()` for clustering features and cells  and `celdaHeatmap()` for displaying expression
36
+}
0 37
new file mode 100755
... ...
@@ -0,0 +1,39 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/all_generics.R
3
+\name{celdaUmap}
4
+\alias{celdaUmap}
5
+\title{Embeds cells in two dimensions using umap.}
6
+\usage{
7
+celdaUmap(counts, celda.mod, max.cells = 25000, min.cluster.size = 100,
8
+  modules = NULL, umap.config = umap::umap.defaults)
9
+}
10
+\arguments{
11
+\item{counts}{Integer matrix. Rows represent features and columns represent cells. This matrix should be the same as the one used to generate `celda.mod`.}
12
+
13
+\item{celda.mod}{Celda object of class `celda_CG`.}
14
+
15
+\item{max.cells}{Integer. Maximum number of cells to plot. Cells will be randomly subsampled if ncol(counts) > max.cells. Larger numbers of cells requires more memory. Default 25000.}
16
+
17
+\item{min.cluster.size}{Integer. Do not subsample cell clusters below this threshold. Default 100.}
18
+
19
+\item{modules}{Integer vector. Determines which features modules to use for tSNE. If NULL, all modules will be used. Default NULL.}
20
+
21
+\item{perplexity}{Numeric. Perplexity parameter for tSNE. Default 20.}
22
+
23
+\item{max.iter}{Integer. Maximum number of iterations in tSNE generation. Default 2500.}
24
+
25
+\item{seed}{Integer. Passed to `set.seed()`. Default 12345. If NULL, no calls to `set.seed()` are made.}
26
+
27
+\item{...}{Additional parameters.}
28
+
29
+\item{...}{Additional parameters.}
30
+}
31
+\value{
32
+Numeric Matrix of dimension `ncol(counts)` x 2, colums representing the "X" and "Y" coordinates in the data's t-SNE represetation.
33
+}
34
+\description{
35
+Embeds cells in two dimensions using umap.
36
+}
37
+\examples{
38
+tsne.res = celdaTsne(celda.CG.sim$counts, celda.CG.mod)
39
+}
... ...
@@ -231,6 +231,27 @@ test_that(desc = "Testing celdaTsne with celda_C including a subset of cells",{
231 231
   expect_true(!is.null(plot.obj))
232 232
 })
233 233
 
234
+test_that(desc = "Testing celdaUmap with celda_C when model class is changed, should error",{
235
+  model_X <- model_C
236
+  class(model_X) <- "celda_X"
237
+  expect_error(celdaUmap(counts=celdaC.sim$counts, celda.mod=model_X, max.cells=length(model_C@clusters$z), min.cluster.size=10), "unable to find")
238
+})
239
+
240
+test_that(desc = "Testing celdaUmap with celda_C including all cells",{
241
+  umap = celdaUmap(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=length(model_C@clusters$z), min.cluster.size=10)
242
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], model_C@clusters$z)
243
+  expect_true(ncol(umap) == 2 & nrow(umap) == length(model_C@clusters$z))
244
+  expect_true(!is.null(plot.obj))
245
+})
246
+
247
+test_that(desc = "Testing celdaUmap with celda_C including a subset of cells",{
248
+  expect_success(expect_error(umap <- celdaUmap(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=50, min.cluster.size=50)))
249
+  umap <- celdaUmap(counts=celdaC.sim$counts, celda.mod=model_C, max.cells=100, min.cluster.size=10)
250
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], model_C@clusters$z)
251
+  expect_true(ncol(umap) == 2 & nrow(umap) == length(model_C@clusters$z) && sum(!is.na(umap[,1])) == 100)
252
+  expect_true(!is.null(plot.obj))
253
+})
254
+
234 255
 # featureModuleLookup
235 256
 test_that(desc = "Testing featureModuleLookup with celda_C", {
236 257
   expect_error(featureModuleLookup(celdaC.sim$counts, model_C, "test_feat"))
... ...
@@ -343,6 +343,32 @@ test_that(desc = "Testing celdaTsne.celda_CG with subset of cells",{
343 343
   expect_true(!is.null(plot.obj))
344 344
 })
345 345
 
346
+# celdaUmap
347
+test_that(desc = "Testing celdaUmap with celda_CG when model class is changed, should error",{
348
+  model_X <- model_CG
349
+  class(model_X) <- "celda_X"
350
+  expect_error(celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_X),
351
+               "unable to find")
352
+})
353
+
354
+test_that(desc = "Testing celdaUmap.celda_CG with all cells",{
355
+  umap = celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=length(model_CG@clusters$z))
356
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], model_CG@clusters$z)
357
+  expect_true(ncol(umap) == 2 & nrow(umap) == length(model_CG@clusters$z))
358
+  expect_true(!is.null(plot.obj))
359
+  
360
+  umap = celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=ncol(celdaCG.sim$counts), modules=1:2)
361
+  expect_error(umap <- celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=ncol(celdaCG.sim$counts), modules=1000:1005))
362
+})
363
+
364
+test_that(desc = "Testing celdaUmap.celda_CG with subset of cells",{
365
+  expect_success(expect_error(umap <- celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=50, min.cluster.size=50)))
366
+  umap = celdaUmap(counts=celdaCG.sim$counts, celda.mod=model_CG, max.cells=100, min.cluster.size=10)
367
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], model_CG@clusters$z)
368
+  expect_true(ncol(umap) == 2 & nrow(umap) == length(model_CG@clusters$z) && sum(!is.na(umap[,1])) == 100)
369
+  expect_true(!is.null(plot.obj))
370
+})
371
+
346 372
 # featureModuleLookup
347 373
 test_that(desc = "Testing featureModuleLookup with celda_CG", {
348 374
   res = featureModuleLookup(celdaCG.sim$counts, model_CG, "Gene_1")
... ...
@@ -230,6 +230,30 @@ test_that(desc = "Testing celdaTsne with celda_G including a subset of cells",{
230 230
   expect_true(!is.null(plot.obj))
231 231
 })
232 232
 
233
+#celdaUmap
234
+test_that(desc = "Testing celdaUmap with celda_G when model class is changed, should error",{
235
+  model_X <- model_G
236
+  class(model_X) <- "celda_X"
237
+  expect_error(celdaUmap(counts=celdaG.sim$counts, celda.mod=model_X), "unable to find")
238
+})
239
+
240
+test_that(desc = "Testing celdaUmap with celda_C including all cells",{
241
+  umap = celdaUmap(counts=celdaG.sim$counts, celda.mod=model_G, max.cells=ncol(celdaG.sim$counts))
242
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], rep(1,ncol(celdaG.sim$counts)))
243
+  expect_true(ncol(umap) == 2 & nrow(umap) == ncol(celdaG.sim$counts))
244
+  expect_true(!is.null(plot.obj))
245
+  
246
+  umap = celdaUmap(counts=celdaG.sim$counts, celda.mod=model_G, max.cells=ncol(celdaG.sim$counts), modules=1:2)
247
+  expect_error(umap <- celdaUmap(counts=celdaG.sim$counts, celda.mod=model_G, max.cells=ncol(celdaG.sim$counts), modules=1000:1005))
248
+})
249
+
250
+test_that(desc = "Testing celdaUmap with celda_G including a subset of cells",{
251
+  umap = celdaUmap(counts=celdaG.sim$counts, celda.mod=model_G, max.cells=100)
252
+  plot.obj = plotDimReduceCluster(umap[,1], umap[,2], rep(1, ncol(celdaG.sim$counts)))
253
+    expect_true(ncol(umap) == 2 & nrow(umap) == ncol(celdaG.sim$counts) && sum(!is.na(umap[,1])) == 100)
254
+  expect_true(!is.null(plot.obj))
255
+})
256
+
233 257
 # featureModuleLookup
234 258
 test_that(desc = "Testing featureModuleLookup with celda_G", {
235 259
   res = featureModuleLookup(celdaG.sim$counts, model_G, "Gene_1")