Browse code

fix package imports

87875172 authored on 23/04/2019 22:21:05
Showing 15 changed files

... ...
@@ -28,7 +28,7 @@ Imports:
28 28
     methods,
29 29
     reshape2,
30 30
     MAST,
31
-    GenomicRanges,
31
+    S4Vectors,
32 32
     data.table,
33 33
     Rcpp,
34 34
     RcppEigen,
... ...
@@ -38,8 +38,7 @@ Imports:
38 38
     SummarizedExperiment,
39 39
     MCMCprecision,
40 40
     ggrepel,
41
-    Rtsne,
42
-    S4Vectors
41
+    Rtsne
43 42
 Suggests:
44 43
     testthat,
45 44
     knitr,
... ...
@@ -76,23 +76,51 @@ exportMethods(perplexity)
76 76
 exportMethods(resList)
77 77
 exportMethods(runParams)
78 78
 exportMethods(sampleLabel)
79
-import(MAST, except = c(combine))
80
-import(RColorBrewer)
81 79
 import(Rcpp)
82 80
 import(RcppEigen)
83
-import(SummarizedExperiment, except = c(shift, rowRanges))
84
-import(data.table)
85
-import(foreach)
86
-import(grDevices)
81
+import(ggplot2)
87 82
 import(graphics)
88
-import(grid)
89
-import(gridExtra)
90 83
 import(gridExtra, except = c(combine))
91
-import(gtable)
92
-import(matrixStats, except = c(count))
93
-import(plyr)
94
-import(scales)
84
+import(stats)
85
+importFrom(MAST,FromMatrix)
86
+importFrom(MAST,summary)
87
+importFrom(MAST,zlm)
88
+importFrom(MCMCprecision,fit_dirichlet)
89
+importFrom(RColorBrewer,brewer.pal)
90
+importFrom(Rtsne,Rtsne)
91
+importFrom(S4Vectors,mcols)
92
+importFrom(SummarizedExperiment,assay)
93
+importFrom(SummarizedExperiment,assayNames)
94
+importFrom(SummarizedExperiment,colData)
95
+importFrom(data.table,as.data.table)
96
+importFrom(digest,digest)
97
+importFrom(doParallel,registerDoParallel)
95 98
 importFrom(enrichR,enrichr)
99
+importFrom(enrichR,listEnrichrDbs)
100
+importFrom(foreach,foreach)
101
+importFrom(ggrepel,geom_text_repel)
102
+importFrom(grDevices,colorRampPalette)
103
+importFrom(grDevices,colors)
104
+importFrom(grDevices,hsv)
105
+importFrom(grDevices,rgb2hsv)
106
+importFrom(grid,grid.draw)
107
+importFrom(grid,grid.newpage)
108
+importFrom(grid,unit)
109
+importFrom(gridExtra,grid.arrange)
110
+importFrom(gtable,gtable)
111
+importFrom(gtable,gtable_add_grob)
112
+importFrom(gtable,gtable_height)
113
+importFrom(gtable,gtable_width)
114
+importFrom(matrixStats,logSumExp)
115
+importFrom(methods,.hasSlot)
116
+importFrom(methods,is)
117
+importFrom(methods,new)
118
+importFrom(plyr,mapvalues)
119
+importFrom(reshape2,melt)
120
+importFrom(scales,dscale)
121
+importFrom(stringi,stri_list2matrix)
122
+importFrom(umap,umap)
123
+importFrom(umap,umap.defaults)
96 124
 useDynLib(celda,"_colSumByGroup")
97 125
 useDynLib(celda,"_colSumByGroupChange")
98 126
 useDynLib(celda,"_colSumByGroup_numeric")
... ...
@@ -32,6 +32,7 @@
32 32
 #' @examples
33 33
 #' data(celdaCGSim, celdaCGMod)
34 34
 #' moduleHeatmap(celdaCGSim$counts, celdaCGMod)
35
+#' @importFrom methods .hasSlot
35 36
 #' @export
36 37
 moduleHeatmap <- function(counts,
37 38
     celdaMod,
... ...
@@ -327,6 +327,7 @@ setMethod("celdaPerplexity",
327 327
 #' data(celdaCGGridSearchRes)
328 328
 #' appendedList <- appendCeldaList(celdaCGGridSearchRes,
329 329
 #'     celdaCGGridSearchRes)
330
+#' @importFrom methods new
330 331
 #' @export
331 332
 appendCeldaList <- function(list1, list2) {
332 333
     if (!is.element("celdaList", class(list1)) |
... ...
@@ -579,6 +580,7 @@ setGeneric("celdaTsne",
579 580
 #' @examples
580 581
 #' data(celdaCGSim, celdaCGMod)
581 582
 #' tsneRes <- celdaUmap(celdaCGSim$counts, celdaCGMod)
583
+#' @importFrom umap umap.defaults
582 584
 #' @export
583 585
 setGeneric("celdaUmap",
584 586
     signature = "celdaMod",
... ...
@@ -46,7 +46,9 @@
46 46
 #'     bestOnly = TRUE,
47 47
 #'     nchains = 1,
48 48
 #'     cores = 2)
49
-#' @import foreach
49
+#' @importFrom foreach foreach
50
+#' @importFrom doParallel registerDoParallel
51
+#' @importFrom methods is
50 52
 #' @export
51 53
 celdaGridSearch <- function(counts,
52 54
     model,
... ...
@@ -296,7 +298,7 @@ subsetCeldaList <- function(celdaList, params) {
296 298
 #' data(celdaCGGridSearchRes)
297 299
 #' ## Returns same result as running celdaGridSearch with "bestOnly = TRUE"
298 300
 #' cgsBest <- selectBestModel(celdaCGGridSearchRes)
299
-#' @import data.table
301
+#' @importFrom data.table as.data.table
300 302
 #' @export
301 303
 selectBestModel <- function(celdaList) {
302 304
     if (!methods::is(celdaList, "celdaList"))
... ...
@@ -521,6 +521,7 @@ celda_C <- function(counts,
521 521
 #' @examples
522 522
 #' celdaCSim <- simulateCells(model = "celda_C", K = 10)
523 523
 #' simCounts <- celdaCSim$counts
524
+#' @import stats
524 525
 #' @export
525 526
 simulateCellscelda_C <- function(model,
526 527
     S = 5,
... ...
@@ -873,7 +874,7 @@ setMethod("clusterProbability", signature(celdaMod = "celda_C"),
873 874
 #' @examples
874 875
 #' data(celdaCSim, celdaCMod)
875 876
 #' perplexity <- perplexity(celdaCSim$counts, celdaCMod)
876
-#' @rawNamespace import(matrixStats, except = c(count))
877
+#' @importFrom matrixStats logSumExp
877 878
 #' @export
878 879
 setMethod("perplexity", signature(celdaMod = "celda_C"),
879 880
     function(counts, celdaMod, newCounts = NULL) {
... ...
@@ -1131,6 +1132,7 @@ setMethod("celdaUmap", signature(celdaMod = "celda_C"),
1131 1132
 #' data(celdaCSim, celdaCMod)
1132 1133
 #' celdaProbabilityMap(celdaCSim$counts, celdaCMod)
1133 1134
 #' @return A grob containing the specified plots
1135
+#' @importFrom gridExtra grid.arrange
1134 1136
 #' @export
1135 1137
 setMethod("celdaProbabilityMap", signature(celdaMod = "celda_C"),
1136 1138
     function(counts, celdaMod, level = c("sample"), ...) {
... ...
@@ -1108,7 +1108,7 @@ setMethod("clusterProbability", signature(celdaMod = "celda_CG"),
1108 1108
 #' @examples
1109 1109
 #' data(celdaCGSim, celdaCGMod)
1110 1110
 #' perplexity <- perplexity(celdaCGSim$counts, celdaCGMod)
1111
-#' @rawNamespace import(matrixStats, except = c(count))
1111
+#' @importFrom matrixStats logSumExp
1112 1112
 #' @export
1113 1113
 setMethod("perplexity", signature(celdaMod = "celda_CG"),
1114 1114
     function(counts, celdaMod, newCounts = NULL) {
... ...
@@ -1412,7 +1412,9 @@ setMethod("celdaUmap",
1412 1412
 #' data(celdaCGSim, celdaCGMod)
1413 1413
 #' celdaProbabilityMap(celdaCGSim$counts, celdaCGMod)
1414 1414
 #' @return A grob containing the specified plots
1415
-#' @import gridExtra
1415
+#' @importFrom gridExtra grid.arrange
1416
+#' @importFrom RColorBrewer brewer.pal
1417
+#' @importFrom grDevices colorRampPalette
1416 1418
 #' @seealso `celda_CG()` for clustering features and cells
1417 1419
 #' @export
1418 1420
 setMethod("celdaProbabilityMap", signature(celdaMod = "celda_CG"),
... ...
@@ -129,6 +129,7 @@ normalizeCounts <- function(counts,
129 129
 #' @examples
130 130
 #' data(celdaCGMod)
131 131
 #' celdaModReorderedZ <- recodeClusterZ(celdaCGMod, c(1, 3), c(3, 1))
132
+#' @importFrom plyr mapvalues
132 133
 #' @export
133 134
 recodeClusterZ <- function(celdaMod, from, to) {
134 135
     if (length(setdiff(from, to)) != 0) {
... ...
@@ -254,6 +255,9 @@ compareCountMatrix <- function(counts,
254 255
 #' @return A vector of distinct colors that have been converted to HEX from HSV.
255 256
 #' @examples
256 257
 #' colorPal <- distinctColors(6) # can be used in plotting functions
258
+#' @importFrom grDevices colors
259
+#' @importFrom grDevices rgb2hsv
260
+#' @importFrom grDevices hsv
257 261
 #' @export
258 262
 distinctColors <- function(n,
259 263
     hues = c("red",
... ...
@@ -320,6 +324,7 @@ distinctColors <- function(n,
320 324
 
321 325
 # Wrapper function, creates checksum for matrix.
322 326
 # Feature names, cell names are not taken into account.
327
+#' @importFrom digest digest
323 328
 .createCountChecksum <- function(counts) {
324 329
     rownames(counts) <- NULL
325 330
     colnames(counts) <- NULL
... ...
@@ -378,6 +383,7 @@ distinctColors <- function(n,
378 383
 #' @examples
379 384
 #' data(celdaCGSim, celdaCGMod)
380 385
 #' featureModuleTable(celdaCGSim$counts, celdaCGMod, outputFile = NULL)
386
+#' @importFrom stringi stri_list2matrix
381 387
 #' @export
382 388
 featureModuleTable <- function(counts, celdaMod, outputFile = NULL) {
383 389
     factorize.matrix <- factorizeMatrix(counts, celdaMod)
... ...
@@ -421,6 +427,9 @@ featureModuleTable <- function(counts, celdaMod, outputFile = NULL) {
421 427
 #' data(celdaCGSim, celdaCGMod)
422 428
 #' violinPlot(counts = celdaCGSim$counts,
423 429
 #'     celdaMod = celdaCGMod, features = "Gene_1")
430
+#' @import ggplot2
431
+#' @importFrom grid unit
432
+#' @importFrom reshape2 melt
424 433
 #' @export
425 434
 violinPlot <- function(counts,
426 435
     celdaMod,
... ...
@@ -73,12 +73,9 @@
73 73
 #' plotHeatmap(celdaCGSim$counts,
74 74
 #'     z = clusters(celdaCGMod)$z, y = clusters(celdaCGMod)$y)
75 75
 #' @return list A list containing dendrogram information and the heatmap grob
76
-#' @import gtable
77
-#' @import grid
78
-#' @import scales
79
-#' @import RColorBrewer
80
-#' @import grDevices
81 76
 #' @import graphics
77
+#' @importFrom grid grid.newpage
78
+#' @importFrom grid grid.draw
82 79
 #' @export
83 80
 plotHeatmap <- function(counts,
84 81
     z = NULL,
... ...
@@ -118,6 +118,7 @@ simulateContaminatedMatrix <- function(C = 300,
118 118
 #  eta Numeric matrix. Rows represent features and columns represent cell
119 119
 # populations
120 120
 #  theta Numeric vector. Proportion of truely expressed transctripts
121
+#' @importFrom MCMCprecision fit_dirichlet
121 122
 .cDCalcEMDecontamination <- function(counts,
122 123
     phi,
123 124
     eta,
... ...
@@ -498,6 +499,7 @@ decontX <- function(counts,
498 499
 
499 500
 
500 501
 ## Make sure provided cell labels are the right type
502
+#' @importFrom plyr mapvalues
501 503
 .processCellLabels <- function(z, numCells) {
502 504
     if (length(z) != numCells) {
503 505
         stop("'z' must be of the same length as the number of cells in the",
... ...
@@ -26,9 +26,14 @@
26 26
 #' clusterDiffexpRes = differentialExpression(celdaCGSim$counts,
27 27
 #'     celdaCGMod, c1 = c(1, 2))
28 28
 #' @export
29
-#' @import data.table plyr
30
-#' @rawNamespace import(MAST, except = c(combine))
31
-#' @rawNamespace import(SummarizedExperiment, except = c(shift, rowRanges))
29
+#' @importFrom data.table as.data.table
30
+#' @importFrom MAST FromMatrix
31
+#' @importFrom MAST zlm
32
+#' @importFrom MAST summary
33
+#' @importFrom S4Vectors mcols
34
+#' @importFrom SummarizedExperiment assay
35
+#' @importFrom SummarizedExperiment colData
36
+#' @importFrom SummarizedExperiment assayNames
32 37
 differentialExpression <- function(counts,
33 38
     celdaMod,
34 39
     c1,
... ...
@@ -24,6 +24,7 @@
24 24
 #'     cm,
25 25
 #'     databases = c('GO_Biological_Process_2018','GO_Molecular_Function_2018'))
26 26
 #' @importFrom enrichR enrichr
27
+#' @importFrom enrichR listEnrichrDbs
27 28
 #' @export
28 29
 geneSetEnrich <- function(counts, celdaModel, databases, fdr = 0.05) {
29 30
     #check for correct celda object
... ...
@@ -34,6 +34,7 @@
34 34
 #'     colorLow = "grey",
35 35
 #'     colorMid = NULL,
36 36
 #'     colorHigh = "blue")
37
+#' @importFrom reshape2 melt
37 38
 #' @export
38 39
 plotDimReduceGrid <- function(dim1,
39 40
     dim2,
... ...
@@ -321,6 +322,7 @@ plotDimReduceModule <-
321 322
 #'     dim2 = celdaTsne[, 2],
322 323
 #'     cluster = as.factor(clusters(celdaCGMod)$z),
323 324
 #'     specificClusters = c(1, 2, 3))
325
+#' @importFrom ggrepel geom_text_repel
324 326
 #' @export
325 327
 plotDimReduceCluster <- function(dim1,
326 328
     dim2,
... ...
@@ -385,6 +387,7 @@ plotDimReduceCluster <- function(dim1,
385 387
 # dimensionality reduction with PCA before tSNE.
386 388
 # @param initialDims Integer.Number of dimensions from PCA to use as
387 389
 # input in tSNE.
390
+#' @importFrom Rtsne Rtsne
388 391
 .calculateTsne <- function(norm,
389 392
     perplexity = 20,
390 393
     maxIter = 2500,
... ...
@@ -409,6 +412,7 @@ plotDimReduceCluster <- function(dim1,
409 412
 # @param umapConfig An object of class umap.config,
410 413
 # containing configuration parameters to be passed to umap.
411 414
 # Default umap::umap.defualts.
415
+#' @importFrom umap umap
412 416
 .calculateUmap <- function(norm, umapConfig = umap::umap.defaults) {
413 417
     return(umap::umap(norm, umapConfig)$layout)
414 418
 }
... ...
@@ -1,7 +1,7 @@
1 1
 # Adapted originally from the very excellent pheatmap package
2 2
 # (https://cran.r-project.org/web/packages/pheatmap/index.html)
3 3
 
4
-
4
+#' @importFrom gtable gtable
5 5
 .lo <- function(rown,
6 6
     coln,
7 7
     nrow,
... ...
@@ -184,7 +184,7 @@
184 184
     }
185 185
 
186 186
     # Produce gtable
187
-    gt <- gtable(widths = unit.c(treeHeightRow,
187
+    gt <- gtable::gtable(widths = unit.c(treeHeightRow,
188 188
             annotRowWidth,
189 189
             matWidth,
190 190
             rownWidth,
... ...
@@ -582,6 +582,9 @@ vplayout <- function(x, y) {
582 582
     return(viewport(layout.pos.row = x, layout.pos.col = y))
583 583
 }
584 584
 
585
+#' @importFrom gtable gtable_height
586
+#' @importFrom gtable gtable_width
587
+#' @importFrom gtable gtable_add_grob
585 588
 .heatmapMotor <- function(matrix,
586 589
         borderColor,
587 590
         cellWidth,
... ...
@@ -643,12 +646,12 @@ vplayout <- function(x, y) {
643 646
 
644 647
         if (!is.na(fileName)) {
645 648
             if (is.na(height)) {
646
-                height <- convertHeight(gtable_height(res),
649
+                height <- convertHeight(gtable::gtable_height(res),
647 650
                     "inches",
648 651
                     valueOnly = TRUE)
649 652
             }
650 653
             if (is.na(width)) {
651
-                width <- convertWidth(gtable_width(res),
654
+                width <- convertWidth(gtable::gtable_width(res),
652 655
                     "inches",
653 656
                     valueOnly = TRUE)
654 657
             }
... ...
@@ -758,7 +761,7 @@ vplayout <- function(x, y) {
758 761
         # Draw title
759 762
         if (!is.na(main)) {
760 763
             elem <- .drawMain(main, fontSize = 1.3 * fontSize, ...)
761
-            res <- gtable_add_grob(res,
764
+            res <- gtable::gtable_add_grob(res,
762 765
                 elem,
763 766
                 t = 1,
764 767
                 l = 3,
... ...
@@ -769,7 +772,7 @@ vplayout <- function(x, y) {
769 772
         # Draw tree for the columns
770 773
         if (!.is.na2(treeCol) & treeHeightCol != 0) {
771 774
             elem <- .drawDendrogram(treeCol, gapsCol, horizontal = TRUE)
772
-            res <- gtable_add_grob(res,
775
+            res <- gtable::gtable_add_grob(res,
773 776
                 elem,
774 777
                 t = 2,
775 778
                 l = 3,
... ...
@@ -779,7 +782,7 @@ vplayout <- function(x, y) {
779 782
         # Draw tree for the rows
780 783
         if (!.is.na2(treeRow) & treeHeightRow != 0) {
781 784
             elem <- .drawDendrogram(treeRow, gapsRow, horizontal = FALSE)
782
-            res <- gtable_add_grob(res,
785
+            res <- gtable::gtable_add_grob(res,
783 786
                 elem,
784 787
                 t = 4,
785 788
                 l = 1,
... ...
@@ -795,7 +798,7 @@ vplayout <- function(x, y) {
795 798
             fontSizeNumber,
796 799
             numberColor)
797 800
 
798
-        res <- gtable_add_grob(res,
801
+        res <- gtable::gtable_add_grob(res,
799 802
                 elem,
800 803
                 t = 4,
801 804
                 l = 3,
... ...
@@ -809,7 +812,7 @@ vplayout <- function(x, y) {
809 812
                 fontSize = fontSizeCol,
810 813
                 ...)
811 814
             elem <- do.call(.drawColnames, pars)
812
-            res <- gtable_add_grob(res,
815
+            res <- gtable::gtable_add_grob(res,
813 816
                 elem,
814 817
                 t = 5,
815 818
                 l = 3,
... ...
@@ -823,7 +826,7 @@ vplayout <- function(x, y) {
823 826
                 gaps = gapsRow,
824 827
                 fontSize = fontSizeRow, ...)
825 828
             elem <- do.call(.drawRownames, pars)
826
-            res <- gtable_add_grob(res,
829
+            res <- gtable::gtable_add_grob(res,
827 830
                 elem,
828 831
                 t = 4,
829 832
                 l = 4,
... ...
@@ -841,7 +844,7 @@ vplayout <- function(x, y) {
841 844
                 gapsCol,
842 845
                 fontSize,
843 846
                 horizontal = TRUE)
844
-            res <- gtable_add_grob(res,
847
+            res <- gtable::gtable_add_grob(res,
845 848
                 elem,
846 849
                 t = 3,
847 850
                 l = 3,
... ...
@@ -853,7 +856,7 @@ vplayout <- function(x, y) {
853 856
                 elem <- .drawAnnotationNames(annotationCol,
854 857
                     fontSize,
855 858
                     horizontal = TRUE)
856
-                res <- gtable_add_grob(res,
859
+                res <- gtable::gtable_add_grob(res,
857 860
                     elem,
858 861
                     t = 3,
859 862
                     l = 4,
... ...
@@ -872,7 +875,7 @@ vplayout <- function(x, y) {
872 875
                 gapsRow,
873 876
                 fontSize,
874 877
                 horizontal = FALSE)
875
-            res <- gtable_add_grob(res,
878
+            res <- gtable::gtable_add_grob(res,
876 879
                 elem,
877 880
                 t = 4,
878 881
                 l = 2,
... ...
@@ -884,7 +887,7 @@ vplayout <- function(x, y) {
884 887
                 elem <- .drawAnnotationNames(annotationRow,
885 888
                     fontSize,
886 889
                     horizontal = FALSE)
887
-                res <- gtable_add_grob(res,
890
+                res <- gtable::gtable_add_grob(res,
888 891
                     elem,
889 892
                     t = 5,
890 893
                     l = 2,
... ...
@@ -907,7 +910,7 @@ vplayout <- function(x, y) {
907 910
                 ...)
908 911
 
909 912
             t <- ifelse(is.null(labelsRow), 4, 3)
910
-            res <- gtable_add_grob(res,
913
+            res <- gtable::gtable_add_grob(res,
911 914
                 elem,
912 915
                 t = t,
913 916
                 l = 6,
... ...
@@ -921,7 +924,7 @@ vplayout <- function(x, y) {
921 924
             elem <- .drawLegend(color, breaks, legend, fontSize = fontSize, ...)
922 925
 
923 926
             t <- ifelse(is.null(labelsRow), 4, 3)
924
-            res <- gtable_add_grob(res,
927
+            res <- gtable::gtable_add_grob(res,
925 928
                     elem,
926 929
                     t = t,
927 930
                     l = 5,
... ...
@@ -1213,6 +1216,7 @@ vplayout <- function(x, y) {
1213 1216
     return(mat)
1214 1217
 }
1215 1218
 
1219
+#' @importFrom scales dscale
1216 1220
 .generateAnnotationColours <- function(annotation,
1217 1221
     annotationColors,
1218 1222
     drop) {
... ...
@@ -1493,6 +1497,7 @@ vplayout <- function(x, y) {
1493 1497
 #' }
1494 1498
 #'
1495 1499
 #' pheatmap(test, clusteringCallback = callback)
1500
+#' @importFrom RColorBrewer brewer.pal
1496 1501
 semiPheatmap <- function(mat,
1497 1502
     color = colorRampPalette(rev(brewer.pal(n = 7, name = "RdYlBu")))(100),
1498 1503
     kmeansK = NA,
... ...
@@ -16,7 +16,7 @@ vignette: >
16 16
  
17 17
 In this vignette we will demonstrate how to use celda to perform cell and feature clustering with simulated data.
18 18
 
19
-#Installation
19
+# Installation
20 20
 
21 21
 celda can be installed from Bioconductor:
22 22
 
... ...
@@ -38,7 +38,7 @@ Complete list of help files are accessible using the help command with a `packag
38 38
 help(package = celda)
39 39
 ```
40 40
 
41
-To see the latest updates and releases or to post a bug, see our GitHub page at https://github.com/compbiomed/celda. To ask questions about running celda, visit our Google group at https://groups.google.com/forum/#!forum/celda-list. 
41
+To see the latest updates and releases or to post a bug, see our GitHub page at https://github.com/campbio/celda. To ask questions about running celda, post a thread on Bioconductor support site at https://support.bioconductor.org/.
42 42
 
43 43
 <br>
44 44
 
... ...
@@ -191,7 +191,8 @@ celdaProbabilityMap(counts = simCounts$counts, celdaMod = celdaModel)
191 191
 `moduleHeatmap` creates a heatmap using only the features from a specific feature module. Cells are ordered from those with the lowest probability of the module to the highest. If more than one module is used, then cells will be ordered by the probabilities of the first module.
192 192
 
193 193
 ```{r, eval = TRUE, fig.width = 7, fig.height = 7}
194
-moduleHeatmap(counts = simCounts$counts, celdaMod = celdaModel, featureModule = 1, topCells = 100)
194
+moduleHeatmap(counts = simCounts$counts, celdaMod = celdaModel,
195
+    featureModule = 1, topCells = 100)
195 196
 ```
196 197
 
197 198
 While `celdaHeatmap` will plot a heatmap directly with a celda object, the `plotHeatmap` function is a more general heatmap function which takes a normalized expression matrix as the input. Simple normalization of the counts matrix can be performed with the `normalizeCounts` function. For instance, if users want to display specific modules and cell populations, the `featureIx`  and `cells.ix` parameters can be used to select rows and columns out of the matrix. 
... ...
@@ -258,7 +259,7 @@ plotHeatmap(counts = normCounts[, clusters(celdaModel)$z %in% c(1, 2)],
258 259
 
259 260
 # Identifying the optimal number of cell subpopulations and feature modules
260 261
 
261
-In the previous example, the best K(the number of cell clusters) and L(the number of feature modules) was already known. However, the optimal K and L for each new dataset will likely not be known beforehand and multiple choices of K and L may need to be tried and compared. celda offers two sets of functions to determine the optimum K and L, `recursiveSplitModule`/`recursiveSplitCell`, and `celdaGridSearch`.
262
+In the previous example, the best K (the number of cell clusters) and L (the number of feature modules) was already known. However, the optimal K and L for each new dataset will likely not be known beforehand and multiple choices of K and L may need to be tried and compared. celda offers two sets of functions to determine the optimum K and L, `recursiveSplitModule`/`recursiveSplitCell`, and `celdaGridSearch`.
262 263
 
263 264
 ## recursiveSplitModule/recursiveSplitCell
264 265
 
... ...
@@ -271,7 +272,7 @@ moduleSplit <- recursiveSplitModule(counts = simCounts$counts,
271 272
     initialL = 2, maxL = 15)
272 273
 ```
273 274
 
274
-Perplexity is a statistical measure of how well a probability model can predict new data. Lower perplexity indicates a better model. The perplexity of each model can be visualized with `plotGridSearchPerplexity`. In general, visual inspection of the plot can be used to select the optimal number of modules ( L ) or cell populations ( K ) by identifying the "elbow" - where the rate of decrease in the perplexity starts to drop off.
275
+Perplexity is a statistical measure of how well a probability model can predict new data. Lower perplexity indicates a better model. The perplexity of each model can be visualized with `plotGridSearchPerplexity`. In general, visual inspection of the plot can be used to select the optimal number of modules (L) or cell populations (K) by identifying the "elbow" - where the rate of decrease in the perplexity starts to drop off.
275 276
 
276 277
 ```{r}
277 278
 plotGridSearchPerplexity(celdaList = moduleSplit)
... ...
@@ -389,6 +390,8 @@ The model prior to reordering cell labels compared to after reordering cell labe
389 390
 table(clusters(celdaModel)$z, clusters(celdaModelZRecoded)$z)
390 391
 ```
391 392
 
393
+# Session Information
394
+
392 395
 ```{r}
393 396
 sessionInfo()
394 397
 ```