Browse code

Merge pull request #622 from mvfki/devel

Bug fixes and deprecate functions

Joshua D. Campbell authored on 29/09/2022 16:28:57 • GitHub committed on 29/09/2022 16:28:57
Showing 43 changed files

... ...
@@ -177,6 +177,8 @@ export(runMNNCorrect)
177 177
 export(runModelGeneVar)
178 178
 export(runNormalization)
179 179
 export(runPerCellQC)
180
+export(runQuickTSNE)
181
+export(runQuickUMAP)
180 182
 export(runSCANORAMA)
181 183
 export(runSCMerge)
182 184
 export(runScDblFinder)
... ...
@@ -200,6 +202,8 @@ export(runSoupX)
200 202
 export(runTSCAN)
201 203
 export(runTSCANClusterDEAnalysis)
202 204
 export(runTSCANDEG)
205
+export(runTSNE)
206
+export(runUMAP)
203 207
 export(runVAM)
204 208
 export(runWilcox)
205 209
 export(runZINBWaVE)
... ...
@@ -242,6 +246,7 @@ import(DropletUtils)
242 246
 import(GSVAdata)
243 247
 import(SingleCellExperiment)
244 248
 import(fishpond)
249
+importFrom(BiocParallel,SerialParam)
245 250
 importFrom(S4Vectors,"metadata<-")
246 251
 importFrom(S4Vectors,metadata)
247 252
 importFrom(SingleCellExperiment,"counts<-")
... ...
@@ -1,4 +1,5 @@
1 1
 #' @title Stores and returns table of SCTK QC outputs to metadata.
2
+#' @rdname getSampleSummaryStatsTable
2 3
 #' @description  Stores and returns table of QC metrics generated from
3 4
 #'  QC algorithms within the metadata slot of the SingleCellExperiment object.
4 5
 #' @param inSCE Input \linkS4class{SingleCellExperiment} object with saved
... ...
@@ -7,8 +8,10 @@
7 8
 #' that stores the stats table within the metadata of the
8 9
 #' SingleCellExperiment object. Required.
9 10
 #' @param ... Other arguments passed to the function. 
10
-#' @return A matrix/array object. Contains a summary table for QC statistics
11
-#' generated from SingleCellTK.
11
+#' @return For \code{getSampleSummaryStatsTable}, A matrix/array object. 
12
+#' Contains a summary table for QC statistics generated from SingleCellTK. For
13
+#' \code{setSampleSummaryStatsTable<-}, A SingleCellExperiment object where the 
14
+#' summary table is updated in the \code{metadata} slot.
12 15
 #' @examples
13 16
 #' data(scExample, package = "singleCellTK")
14 17
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
... ...
@@ -17,18 +20,13 @@
17 20
 #' @export
18 21
 setGeneric("getSampleSummaryStatsTable", function(inSCE, statsName, ...) standardGeneric("getSampleSummaryStatsTable"))
19 22
 
20
-#' @title Setter function which stores table of SCTK QC outputs to metadata.
21
-#' @description  Stores table of QC metrics generated from
22
-#'  QC algorithms within the metadata slot of the SingleCellExperiment object.
23
-#' @param inSCE Input \linkS4class{SingleCellExperiment} object with saved
24
-#' \link{assay} data and/or \link{colData} data. Required.
25
-#' @param value The sample summary table of SCTK QC outputs 
26
-#' @param ... Other arguments passed to the function. 
27
-#' @return A SingleCellExperiment object which contains a summary table for QC statistics
28
-#' generated from SingleCellTK.
29
-setGeneric("setSampleSummaryStatsTable<-", function(inSCE, ..., value) standardGeneric("setSampleSummaryStatsTable<-"))
23
+#' @rdname getSampleSummaryStatsTable
24
+#' @param value The summary table for QC statistics generated from SingleCellTK
25
+#' to be added to the SCE object.
26
+setGeneric("setSampleSummaryStatsTable<-", function(inSCE, statsName, ..., value) standardGeneric("setSampleSummaryStatsTable<-"))
30 27
 
31 28
 #' @title Lists the table of SCTK QC outputs stored within the metadata.
29
+#' @rdname listSampleSummaryStatsTables
32 30
 #' @description  Returns a character vector of the tables
33 31
 #' within the metadata slot of the SingleCellExperiment object.
34 32
 #' @param inSCE Input \linkS4class{SingleCellExperiment} object with saved
... ...
@@ -195,7 +195,7 @@ setTopHVG <- function(inSCE,
195 195
     return(df)
196 196
 }
197 197
 
198
-#' parse `useFeatureSubset` in other functions such as `scaterPCA`, `getUMAP`..
198
+#' parse `useFeatureSubset` in other functions such as `scaterPCA`, `runUMAP`..
199 199
 #' Do checks, and return logical vector. Or character vector as needed by Seurat
200 200
 #' methods
201 201
 #' @param inSCE Input \linkS4class{SingleCellExperiment} object
... ...
@@ -579,8 +579,7 @@ plotBarcodeRankDropsResults <- function(inSCE,
579 579
 #' data(scExample, package="singleCellTK")
580 580
 #' \dontrun{
581 581
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
582
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
583
-#'                reducedDimName="UMAP")
582
+#' sce <- runQuickUMAP(sce)
584 583
 #' sce <- runScrublet(sce)
585 584
 #' plotScrubletResults(inSCE=sce, reducedDimName="UMAP")
586 585
 #' }
... ...
@@ -878,8 +877,7 @@ plotScrubletResults <- function(inSCE,
878 877
 #' @examples
879 878
 #' data(scExample, package="singleCellTK")
880 879
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
881
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
882
-#'                reducedDimName="UMAP")
880
+#' sce <- runQuickUMAP(sce)
883 881
 #' sce <- runDoubletFinder(sce)
884 882
 #' plotDoubletFinderResults(inSCE=sce, reducedDimName="UMAP")
885 883
 #' @export
... ...
@@ -1262,8 +1260,7 @@ plotDoubletFinderResults <- function(inSCE,
1262 1260
 #' @examples
1263 1261
 #' data(scExample, package="singleCellTK")
1264 1262
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
1265
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
1266
-#'                reducedDimName="UMAP")
1263
+#' sce <- runQuickUMAP(sce)
1267 1264
 #' sce <- runScDblFinder(sce)
1268 1265
 #' plotScDblFinderResults(inSCE=sce, reducedDimName="UMAP")
1269 1266
 #' @export
... ...
@@ -1568,8 +1565,7 @@ plotScDblFinderResults <- function(inSCE,
1568 1565
 #' @examples
1569 1566
 #' data(scExample, package="singleCellTK")
1570 1567
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
1571
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
1572
-#'                reducedDimName="UMAP")
1568
+#' sce <- runQuickUMAP(sce)
1573 1569
 #' sce <- runCxds(sce)
1574 1570
 #' plotCxdsResults(inSCE=sce, reducedDimName="UMAP")
1575 1571
 #' @export
... ...
@@ -1871,8 +1867,7 @@ plotCxdsResults <- function(inSCE,
1871 1867
 #' @examples
1872 1868
 #' data(scExample, package="singleCellTK")
1873 1869
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
1874
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
1875
-#'                reducedDimName="UMAP")
1870
+#' sce <- runQuickUMAP(sce)
1876 1871
 #' sce <- runBcds(sce)
1877 1872
 #' plotBcdsResults(inSCE=sce, reducedDimName="UMAP")
1878 1873
 #' @export
... ...
@@ -2175,8 +2170,7 @@ plotBcdsResults <- function(inSCE,
2175 2170
 #' @examples
2176 2171
 #' data(scExample, package="singleCellTK")
2177 2172
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
2178
-#' sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
2179
-#'                reducedDimName="UMAP")
2173
+#' sce <- runQuickUMAP(sce)
2180 2174
 #' sce <- runCxdsBcdsHybrid(sce)
2181 2175
 #' plotScdsHybridResults(inSCE=sce, reducedDimName="UMAP")
2182 2176
 #' @export
... ...
@@ -91,7 +91,7 @@ reportCellQC <- function(inSCE, output_file = NULL,
91 91
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
92 92
 #' \dontrun{
93 93
 #' sce <- runDecontX(sce)
94
-#' sce <- getUMAP(sce, useAssay = "counts", logNorm = TRUE)
94
+#' sce <- runQuickUMAP(sce)
95 95
 #' reportQCTool(inSCE = sce, algorithm = "DecontX")
96 96
 #' }
97 97
 #' @export
... ...
@@ -124,7 +124,8 @@ plotBatchCorrCompare <- function(inSCE, corrMat, batch = NULL, condition = NULL,
124 124
                                  title = "Batch Variance before correction") +
125 125
     ggplot2::theme(text=ggplot2::element_text(size=10))
126 126
 
127
-  inSCE <- getUMAP(inSCE, useAssay = origAssay, reducedDimName = "umap.before")
127
+  inSCE <- runUMAP(inSCE, useAssay = origAssay, useReducedDim = NULL, 
128
+                   reducedDimName = "umap.before")
128 129
   umap.before <- plotSCEDimReduceColData(inSCE, batch, "umap.before",
129 130
                                          shape = condition, axisLabelSize = 9,
130 131
                                          axisSize = 8, dotSize = 1,
... ...
@@ -145,10 +146,11 @@ plotBatchCorrCompare <- function(inSCE, corrMat, batch = NULL, condition = NULL,
145 146
       ggplot2::theme(text=ggplot2::element_text(size=10))
146 147
 
147 148
     if (method == "ComBatSeq") {
148
-      inSCE <- getUMAP(inSCE, useAssay = corrMat, logNorm = TRUE,
149
-                       reducedDimName = "umap.after")
149
+      inSCE <- runUMAP(inSCE, useAssay = corrMat, useReducedDim = NULL, 
150
+                       logNorm = TRUE, reducedDimName = "umap.after")
150 151
     } else {
151
-      inSCE <- getUMAP(inSCE, useAssay = corrMat, reducedDimName = "umap.after")
152
+      inSCE <- runUMAP(inSCE, useAssay = corrMat, useReducedDim = NULL,
153
+                       logNorm = FALSE, reducedDimName = "umap.after")
152 154
     }
153 155
   } else if (matType == "altExp") {
154 156
     # Doing log, because only Seurat returns altExp,
... ...
@@ -161,8 +163,8 @@ plotBatchCorrCompare <- function(inSCE, corrMat, batch = NULL, condition = NULL,
161 163
                                   title = paste0("Batch Variance corrected with ",
162 164
                                                  method)) +
163 165
       ggplot2::theme(text=ggplot2::element_text(size=10))
164
-    inSCE <- getUMAP(inSCE, useAltExp = corrMat, useAssay = corrMat,
165
-                     reducedDimName = "umap.after")
166
+    inSCE <- runQuickUMAP(inSCE, useAssay = corrMat, useAltExp = corrMat, 
167
+                          reducedDimName = "umap.after")
166 168
   } else if (matType == "reducedDim") {
167 169
     bv.after <- plotBatchVariance(inSCE, useReddim = corrMat, batch = batch,
168 170
                                   condition = condition,
... ...
@@ -173,7 +175,7 @@ plotBatchCorrCompare <- function(inSCE, corrMat, batch = NULL, condition = NULL,
173 175
       SingleCellExperiment::reducedDim(inSCE, "umap.after") <-
174 176
         SingleCellExperiment::reducedDim(inSCE, corrMat)
175 177
     } else {
176
-      inSCE <- getUMAP(inSCE, useReducedDim = corrMat,
178
+      inSCE <- runUMAP(inSCE, useReducedDim = corrMat,
177 179
                        reducedDimName = "umap.after")
178 180
     }
179 181
   } else {
... ...
@@ -16,16 +16,16 @@
16 16
 #' data("mouseBrainSubsetSCE")
17 17
 #' plotTSNE(mouseBrainSubsetSCE, colorBy = "level1class",
18 18
 #'          reducedDimName = "TSNE_counts")
19
-plotTSNE <- function(inSCE, colorBy=NULL, shape=NULL,
20
-                     reducedDimName="TSNE", runTSNE=FALSE,
21
-                     useAssay="logcounts"){
19
+plotTSNE <- function(inSCE, colorBy = NULL, shape = NULL,
20
+                     reducedDimName = "TSNE", runTSNE = FALSE,
21
+                     useAssay = "counts"){
22 22
   if(!(reducedDimName %in% names(SingleCellExperiment::reducedDims(inSCE)))){
23 23
     if (runTSNE){
24
-      inSCE <- getTSNE(inSCE, useAssay = useAssay,
25
-                       reducedDimName = reducedDimName)
24
+      inSCE <- runQuickTSNE(inSCE, useAssay = useAssay,
25
+                            reducedDimName = reducedDimName)
26 26
     } else {
27 27
       stop(reducedDimName,
28
-           " dimension not found. Run getTSNE() or set runTSNE to TRUE.")
28
+           " dimension not found. Run `runTSNE()` or set `runTSNE` to `TRUE`.")
29 29
     }
30 30
   }
31 31
   tsneDf <- data.frame(SingleCellExperiment::reducedDim(inSCE,
... ...
@@ -16,18 +16,18 @@
16 16
 #' @examples
17 17
 #' data(scExample, package = "singleCellTK")
18 18
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
19
-#' sce <- getUMAP(inSCE = sce, useAssay = "counts", reducedDimName = "UMAP")
19
+#' sce <- runQuickUMAP(sce)
20 20
 #' plotUMAP(sce)
21 21
 plotUMAP <- function(inSCE, colorBy = NULL, shape = NULL,
22 22
                      reducedDimName = "UMAP", runUMAP = FALSE,
23
-                     useAssay = "logcounts"){
23
+                     useAssay = "counts"){
24 24
   if(!(reducedDimName %in% names(SingleCellExperiment::reducedDims(inSCE)))){
25 25
     if (runUMAP){
26
-      inSCE <- getUMAP(inSCE, useAssay = useAssay,
27
-                       reducedDimName = reducedDimName)
26
+      inSCE <- runQuickUMAP(inSCE, useAssay = useAssay,
27
+                            reducedDimName = reducedDimName)
28 28
     } else {
29 29
       stop(reducedDimName,
30
-           " dimension not found. Run getUMAP() or set runUMAP to TRUE.")
30
+           " dimension not found. Run `runUMAP()` or set `runUMAP` to `TRUE`.")
31 31
     }
32 32
   }
33 33
   UMAPDf <- data.frame(SingleCellExperiment::reducedDim(inSCE,
... ...
@@ -1,8 +1,8 @@
1 1
 #' Generic Wrapper function for running dimensionality reduction
2 2
 #' @details Wrapper function to run one of the available dimensionality
3 3
 #' reduction algorithms integrated within SCTK from \code{\link{scaterPCA}},
4
-#' \code{\link{runSeuratPCA}}, \code{\link{runSeuratICA}}, \code{\link{getTSNE}},
5
-#' \code{\link{runSeuratTSNE}}, \code{\link{getUMAP}} and
4
+#' \code{\link{runSeuratPCA}}, \code{\link{runSeuratICA}}, \code{\link{runTSNE}},
5
+#' \code{\link{runSeuratTSNE}}, \code{\link{runUMAP}} and
6 6
 #' \code{\link{runSeuratUMAP}}. Users can use an assay by specifying
7 7
 #' \code{useAssay}, use the assay in an altExp by specifying both
8 8
 #' \code{useAltExp} and \code{useAssay}, or use a low-dimensionality
... ...
@@ -72,12 +72,12 @@ runDimReduce <- function(inSCE,
72 72
                        useFeatureSubset = useFeatureSubset, scale = scale,
73 73
                        seed = seed, ...)
74 74
   } else if (method == "scaterUMAP") {
75
-    inSCE <- getUMAP(inSCE = inSCE, useAssay = useAssay, useAltExp = useAltExp,
75
+    inSCE <- runUMAP(inSCE = inSCE, useAssay = useAssay, useAltExp = useAltExp,
76 76
                      useReducedDim = useReducedDim,
77 77
                      useFeatureSubset = useFeatureSubset, scale = scale,
78 78
                      reducedDimName = reducedDimName, seed = seed, ...)
79 79
   } else if (method == "rTSNE") {
80
-    inSCE <- getTSNE(inSCE = inSCE, useAssay = useAssay, useAltExp = useAltExp,
80
+    inSCE <- runTSNE(inSCE = inSCE, useAssay = useAssay, useAltExp = useAltExp,
81 81
                      useReducedDim = useReducedDim,
82 82
                      useFeatureSubset = useFeatureSubset, scale = scale,
83 83
                      reducedDimName = reducedDimName, seed = seed, ...)
... ...
@@ -68,9 +68,12 @@ runFindMarker <- function(inSCE, useAssay = 'logcounts',
68 68
                           minMeanExpr = NULL, detectThresh = 0){
69 69
   method <- match.arg(method)
70 70
   # Input checks will be done in `runDEAnalysis()`
71
-  if (is.character(cluster) && length(cluster) == 1) clusterName <- cluster
72
-  else clusterName <- 'findMarker_cluster'
73 71
   clusterVar <- .manageCellVar(inSCE, var = cluster)
72
+  if (is.character(cluster) && length(cluster) == 1) clusterName <- cluster
73
+  else {
74
+    clusterName <- 'findMarker_cluster'
75
+    inSCE[[clusterName]] <- cluster
76
+  }
74 77
   # Iterate
75 78
   if(is.factor(clusterVar)){
76 79
     # In case inSCE is a subset, when "levels" is a full list of all
... ...
@@ -360,9 +360,8 @@ runSoupX <- function(inSCE,
360 360
     out <- SoupX::adjustCounts(sc, method = adjustMethod,
361 361
                                roundToInt = roundToInt, tol = tol, pCut = pCut)
362 362
     message(paste0(date(), " ... Generating UMAP"))
363
-    # Most of time `useAssay` should be "counts", thus logNorm=TRUE
364
-    inSCE <- getUMAP(inSCE, useAssay = useAssay, logNorm = TRUE,
365
-                     reducedDimName = "sampleUMAP")
363
+    inSCE <- runQuickUMAP(inSCE, useAssay = useAssay, sample = NULL,
364
+                          reducedDimName = "sampleUMAP")
366 365
     return(list(sc = sc, out = out,
367 366
                 umap = SingleCellExperiment::reducedDim(inSCE, "sampleUMAP")))
368 367
 }
369 368
similarity index 77%
370 369
rename from R/getTSNE.R
371 370
rename to R/runTSNE.R
... ...
@@ -1,4 +1,5 @@
1 1
 #' Run t-SNE embedding with Rtsne method
2
+#' @rdname runTSNE
2 3
 #' @description T-Stochastic Neighbour Embedding (t-SNE) algorithm is commonly
3 4
 #' for 2D visualization of single-cell data. This function wraps the
4 5
 #' Rtsne \code{\link[Rtsne]{Rtsne}} function.
... ...
@@ -9,18 +10,18 @@
9 10
 #' input, so that the result can match with the clustering based on the same
10 11
 #' input PCA, and will be much faster.
11 12
 #' @param inSCE Input \linkS4class{SingleCellExperiment} object.
13
+#' @param useReducedDim The low dimension representation to use for UMAP
14
+#' computation. Default \code{"PCA"}.
12 15
 #' @param useAssay Assay to use for tSNE computation. If \code{useAltExp} is
13 16
 #' specified, \code{useAssay} has to exist in
14
-#' \code{assays(altExp(inSCE, useAltExp))}. Default \code{"logcounts"}.
15
-#' @param useReducedDim The low dimension representation to use for UMAP
16
-#' computation. Default \code{NULL}.
17
+#' \code{assays(altExp(inSCE, useAltExp))}. Default \code{NULL}.
17 18
 #' @param useAltExp The subset to use for tSNE computation, usually for the
18 19
 #' selected.variable features. Default \code{NULL}.
19 20
 #' @param reducedDimName a name to store the results of the dimension
20 21
 #' reductions. Default \code{"TSNE"}.
21 22
 #' @param logNorm Whether the counts will need to be log-normalized prior to
22 23
 #' generating the tSNE via \code{\link{scaterlogNormCounts}}. Ignored when using
23
-#' \code{useReducedDim}. Default \code{FALSE}.
24
+#' \code{useReducedDim}. Default \code{TRUE}.
24 25
 #' @param useFeatureSubset Subset of feature to use for dimension reduction. A
25 26
 #' character string indicating a \code{rowData} variable that stores the logical
26 27
 #' vector of HVG selection, or a vector that can subset the rows of
... ...
@@ -56,23 +57,24 @@
56 57
 #' data(scExample, package = "singleCellTK")
57 58
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
58 59
 #' # Run from raw counts
59
-#' sce <- getTSNE(inSCE = sce, useAssay = "counts", logNorm = TRUE, nTop = 2000,
60
-#'                scale = TRUE, pca = TRUE)
60
+#' sce <- runQuickTSNE(sce)
61 61
 #' \dontrun{
62 62
 #' # Run from PCA
63 63
 #' sce <- scaterlogNormCounts(sce, "logcounts")
64 64
 #' sce <- runModelGeneVar(sce)
65
+#' sce <- setTopHVG(sce, method = "modelGeneVar", hvgNumber = 2000, 
66
+#'                  featureSubsetName = "HVG_modelGeneVar2000")
65 67
 #' sce <- scaterPCA(sce, useAssay = "logcounts",
66 68
 #'                  useFeatureSubset = "HVG_modelGeneVar2000", scale = TRUE)
67
-#' sce <- getTSNE(sce, useReducedDim = "PCA")
69
+#' sce <- runTSNE(sce, useReducedDim = "PCA")
68 70
 #' }
69 71
 #' @importFrom S4Vectors metadata<-
70
-getTSNE <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
71
-                    useAltExp = NULL, reducedDimName = "TSNE", logNorm = FALSE,
72
+runTSNE <- function(inSCE, useReducedDim = "PCA", useAssay = NULL, 
73
+                    useAltExp = NULL, reducedDimName = "TSNE", logNorm = TRUE,
72 74
                     useFeatureSubset = NULL, nTop = 2000, center = TRUE,
73 75
                     scale = TRUE, pca = TRUE, partialPCA = FALSE,
74 76
                     initialDims = 25, theta = 0.5, perplexity = 30,
75
-                    nIterations = 1000, numThreads = 1, seed = NULL){
77
+                    nIterations = 1000, numThreads = 1, seed = NULL) {
76 78
   params <- as.list(environment())
77 79
   params$inSCE <- NULL
78 80
   # Note: useMat = list(useAssay = useAssay, ...)
... ...
@@ -84,13 +86,13 @@ getTSNE <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
84 86
                              returnMatrix = FALSE)$names
85 87
   params$useAssay <- useMat$useAssay
86 88
   useAssay <- useMat$useAssay
87
-
89
+  
88 90
   if (!is.null(useAltExp)) {
89 91
     sce <- SingleCellExperiment::altExp(inSCE, useAltExp)
90 92
   } else {
91 93
     sce <- inSCE
92 94
   }
93
-
95
+  
94 96
   if (!is.null(useAssay)) {
95 97
     if (isTRUE(logNorm)) {
96 98
       sce <- scaterlogNormCounts(sce, assayName = "logcounts", useAssay = useAssay)
... ...
@@ -125,7 +127,7 @@ getTSNE <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
125 127
       mat <- mat[,seq(initialDims)]
126 128
     }
127 129
   }
128
-
130
+  
129 131
   if (is.null(perplexity)){
130 132
     perplexity <- floor(ncol(inSCE) / 5)
131 133
   }
... ...
@@ -147,3 +149,36 @@ getTSNE <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
147 149
   metadata(inSCE)$sctk$runDimReduce$embedding[[reducedDimName]] <- params
148 150
   return(inSCE)
149 151
 }
152
+
153
+#' @rdname runTSNE
154
+#' @param ... Other parameters to be passed to \code{runTSNE}
155
+#' @export
156
+runQuickTSNE <- function(inSCE, useAssay = "counts", ...) {
157
+  args <- list(...)
158
+  if (!is.null(args$useReducedDim)) {
159
+    warning("Forcing `useReducedDim` to be `NULL`. Please use `runTSNE` for ",
160
+            "using reducedDim.")
161
+  }
162
+  args$useReducedDim <- NULL
163
+  args <- c(list(inSCE = inSCE, useAssay = useAssay, useReducedDim = NULL), 
164
+            args)
165
+  inSCE <- do.call("runTSNE", args = args)
166
+  return(inSCE)
167
+}
168
+
169
+#' @rdname runTSNE
170
+#' @export
171
+getTSNE <- function(inSCE, useReducedDim = "PCA", useAssay = NULL, 
172
+                    useAltExp = NULL, reducedDimName = "TSNE", logNorm = TRUE,
173
+                    useFeatureSubset = NULL, nTop = 2000, center = TRUE,
174
+                    scale = TRUE, pca = TRUE, partialPCA = FALSE,
175
+                    initialDims = 25, theta = 0.5, perplexity = 30,
176
+                    nIterations = 1000, numThreads = 1, seed = NULL) {
177
+  .Deprecated("runTSNE")
178
+  runTSNE(inSCE = inSCE, useReducedDim = useReducedDim, useAssay = useAssay, 
179
+          useAltExp = useAltExp, reducedDimName = reducedDimName, 
180
+          logNorm = logNorm, useFeatureSubset = useFeatureSubset, nTop = nTop, 
181
+          center = center, scale = scale, pca = pca, partialPCA = partialPCA,
182
+          initialDims = initialDims, theta = theta, perplexity = perplexity,
183
+          nIterations = nIterations, numThreads = numThreads, seed = seed)
184
+}
150 185
similarity index 71%
151 186
rename from R/getUMAP.R
152 187
rename to R/runUMAP.R
... ...
@@ -1,21 +1,26 @@
1 1
 #' Run UMAP embedding with scater method
2
+#' @rdname runUMAP
2 3
 #' @description Uniform Manifold Approximation and Projection (UMAP) algorithm
3
-#' is commonly for 2D visualization of single-cell data. This function wraps the
4
-#' scater \code{\link[scater]{calculateUMAP}} function.
5
-#'
6
-#' With this funciton, users can create UMAP embedding directly from raw count
7
-#' matrix, with necessary preprocessing including normalization, scaling,
8
-#' dimension reduction all automated. Yet we still recommend having the PCA as
9
-#' input, so that the result can match with the clustering based on the same
10
-#' input PCA.
4
+#' is commonly for 2D visualization of single-cell data. These functions wrap 
5
+#' the scater \code{\link[scater]{calculateUMAP}} function.
6
+#' 
7
+#' Users can use \code{runQuickUMAP} to directly create UMAP embedding from raw
8
+#' count matrix, with necessary preprocessing including normalization, variable
9
+#' feature selection, scaling, dimension reduction all automated. Therefore, 
10
+#' \code{useReducedDim} is disabled for \code{runQuickUMAP}. 
11
+#' 
12
+#' In a complete analysis, we still recommend having dimension reduction such as
13
+#' PCA created beforehand and select proper numbers of dimensions for using
14
+#' \code{runUMAP}, so that the result can match with the clustering based on the
15
+#' same input PCA. 
11 16
 #' @param inSCE Input \linkS4class{SingleCellExperiment} object.
17
+#' @param useReducedDim The low dimension representation to use for UMAP
18
+#' computation. If \code{useAltExp} is specified, \code{useReducedDim} has to
19
+#' exist in \code{reducedDims(altExp(inSCE, useAltExp))}. Default \code{"PCA"}.
12 20
 #' @param useAssay Assay to use for UMAP computation. If \code{useAltExp} is
13 21
 #' specified, \code{useAssay} has to exist in
14 22
 #' \code{assays(altExp(inSCE, useAltExp))}. Ignored when using
15
-#' \code{useReducedDim}. Default \code{"logcounts"}.
16
-#' @param useReducedDim The low dimension representation to use for UMAP
17
-#' computation. If \code{useAltExp} is specified, \code{useReducedDim} has to
18
-#' exist in \code{reducedDims(altExp(inSCE, useAltExp))}. Default \code{NULL}.
23
+#' \code{useReducedDim}. Default \code{NULL}.
19 24
 #' @param useAltExp The subset to use for UMAP computation, usually for the
20 25
 #' selected variable features. Default \code{NULL}.
21 26
 #' @param sample Character vector. Indicates which sample each cell belongs to.
... ...
@@ -25,7 +30,7 @@
25 30
 #' coordinates obtained from this method. Default \code{"UMAP"}.
26 31
 #' @param logNorm Whether the counts will need to be log-normalized prior to
27 32
 #' generating the UMAP via \code{\link{scaterlogNormCounts}}. Ignored when using
28
-#' \code{useReducedDim}. Default \code{FALSE}.
33
+#' \code{useReducedDim}. Default \code{TRUE}.
29 34
 #' @param useFeatureSubset Subset of feature to use for dimension reduction. A
30 35
 #' character string indicating a \code{rowData} variable that stores the logical
31 36
 #' vector of HVG selection, or a vector that can subset the rows of
... ...
@@ -67,23 +72,23 @@
67 72
 #' data(scExample, package = "singleCellTK")
68 73
 #' sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
69 74
 #' # Run from raw counts
70
-#' sce <- getUMAP(inSCE = sce, useAssay = "counts", logNorm = TRUE, nTop = 2000,
71
-#'                scale = TRUE, pca = TRUE)
75
+#' sce <- runQuickUMAP(sce)
72 76
 #' \dontrun{
73 77
 #' # Run from PCA
74 78
 #' sce <- scaterlogNormCounts(sce, "logcounts")
75 79
 #' sce <- runModelGeneVar(sce)
76 80
 #' sce <- scaterPCA(sce, useAssay = "logcounts",
77 81
 #'                  useFeatureSubset = "HVG_modelGeneVar2000", scale = TRUE)
78
-#' sce <- getUMAP(sce, useReducedDim = "PCA")
82
+#' sce <- runUMAP(sce, useReducedDim = "PCA")
79 83
 #' }
80 84
 #' @importFrom S4Vectors metadata<-
81
-getUMAP <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
85
+#' @importFrom BiocParallel SerialParam
86
+runUMAP <- function(inSCE, useReducedDim = "PCA", useAssay = NULL, 
82 87
                     useAltExp = NULL, sample = NULL, reducedDimName = "UMAP",
83
-                    logNorm = FALSE, useFeatureSubset = NULL, nTop = 2000,
88
+                    logNorm = TRUE, useFeatureSubset = NULL, nTop = 2000,
84 89
                     scale = TRUE, pca = TRUE, initialDims = 25, nNeighbors = 30,
85 90
                     nIterations = 200, alpha = 1, minDist = 0.01, spread = 1,
86
-                    seed = NULL, BPPARAM = BiocParallel::SerialParam()) {
91
+                    seed = NULL, BPPARAM = SerialParam()) {
87 92
   params <- as.list(environment())
88 93
   params$inSCE <- NULL
89 94
   params$BPPARAM <- NULL
... ...
@@ -120,7 +125,7 @@ getUMAP <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
120 125
     if (!isTRUE(pca) & !is.null(useAssay)) {
121 126
       initialDims <- NULL
122 127
     }
123
-
128
+    
124 129
     nNeighbors <- min(ncol(sceSample), nNeighbors)
125 130
     message(paste0(date(), " ... Computing Scater UMAP for sample '",
126 131
                    samples[i], "'."))
... ...
@@ -145,3 +150,39 @@ getUMAP <- function(inSCE, useAssay = "logcounts", useReducedDim = NULL,
145 150
   metadata(inSCE)$sctk$runDimReduce$embedding[[reducedDimName]] <- params
146 151
   return(inSCE)
147 152
 }
153
+
154
+#' @rdname runUMAP
155
+#' @param ... Parameters passed to \code{runUMAP}
156
+#' @importFrom BiocParallel SerialParam
157
+#' @export
158
+runQuickUMAP <- function(inSCE, useAssay = "counts", sample = "sample", ...) {
159
+  args <- list(...)
160
+  if (!is.null(args$useReducedDim)) {
161
+    warning("Forcing `useReducedDim` to be `NULL`. Please use `runUMAP` for ",
162
+            "using reducedDim.")
163
+  }
164
+  args$useReducedDim <- NULL
165
+  args <- c(list(inSCE = inSCE, useAssay = useAssay, useReducedDim = NULL), 
166
+            args)
167
+  inSCE <- do.call("runUMAP", args = args)
168
+  return(inSCE)
169
+}
170
+
171
+#' @rdname runUMAP
172
+#' @export
173
+#' @importFrom BiocParallel SerialParam
174
+getUMAP <- function(inSCE, useReducedDim = "PCA", useAssay = NULL, 
175
+                    useAltExp = NULL, sample = NULL, reducedDimName = "UMAP",
176
+                    logNorm = TRUE, useFeatureSubset = NULL, nTop = 2000,
177
+                    scale = TRUE, pca = TRUE, initialDims = 25, nNeighbors = 30,
178
+                    nIterations = 200, alpha = 1, minDist = 0.01, spread = 1,
179
+                    seed = NULL, BPPARAM = SerialParam()) {
180
+  .Deprecated("runUMAP")
181
+  runUMAP(inSCE, useReducedDim = useReducedDim, useAssay = useAssay, 
182
+          useAltExp = useAltExp, sample = sample, 
183
+          reducedDimName = reducedDimName,
184
+          logNorm = logNorm, useFeatureSubset = useFeatureSubset, nTop = nTop,
185
+          scale = scale, pca = pca, initialDims = initialDims, 
186
+          nNeighbors = nNeighbors, nIterations = nIterations, alpha = alpha, 
187
+          minDist = minDist, spread = spread, seed = seed, BPPARAM = BPPARAM)
188
+}
... ...
@@ -1,4 +1,5 @@
1 1
 #' @rdname getSampleSummaryStatsTable
2
+#' @importFrom S4Vectors metadata
2 3
 setMethod("getSampleSummaryStatsTable", "SingleCellExperiment", function(inSCE, statsName, ...){
3 4
     allStatsNames <- listSampleSummaryStatsTables(inSCE)
4 5
     if(!statsName %in% allStatsNames){
... ...
@@ -6,28 +7,30 @@ setMethod("getSampleSummaryStatsTable", "SingleCellExperiment", function(inSCE,
6 7
                    "The following are the names of the tables stored:",
7 8
                    paste(allStatsNames, collapse = ",")))
8 9
     }else{
9
-        return(inSCE@metadata$sctk$sample_summary[[statsName]])
10
+        return(metadata(inSCE)$sctk$sample_summary[[statsName]])
10 11
     }
11 12
 })
12 13
 
13
-#' @rdname setSampleSummaryStatsTable<-
14
+#' @rdname getSampleSummaryStatsTable
15
+#' @importFrom S4Vectors metadata
14 16
 setReplaceMethod("setSampleSummaryStatsTable", c("SingleCellExperiment", "ANY"), function(inSCE, statsName, ..., value) {
15
-    inSCE@metadata$sctk$sample_summary[[statsName]] <- value
17
+    metadata(inSCE)$sctk$sample_summary[[statsName]] <- value
16 18
     return(inSCE)
17 19
 })
18 20
 
19 21
 #' @rdname listSampleSummaryStatsTables
22
+#' @importFrom S4Vectors metadata
20 23
 setMethod("listSampleSummaryStatsTables", "SingleCellExperiment", function(inSCE, ...){
21
-    if(is.null(inSCE@metadata$sctk$sample_summary)){
24
+    if(is.null(metadata(inSCE)$sctk$sample_summary)){
22 25
         stop(paste("No sample-level QC tables are available.",
23 26
                      "Please try executing functions such as sampleSummaryStats first."))
24 27
     }else{
25
-        allStatsNames <- names(inSCE@metadata$sctk$sample_summary)
28
+        allStatsNames <- names(metadata(inSCE)$sctk$sample_summary)
26 29
         if(is.null(allStatsNames) || length(allStatsNames) == 0){
27 30
             stop(paste("No sample-level QC tables are available.",
28 31
                          "Please try executing functions such as sampleSummaryStats first."))
29 32
         }else{
30
-            return(names(inSCE@metadata$sctk$sample_summary))
33
+            return(names(metadata(inSCE)$sctk$sample_summary))
31 34
         }
32 35
     }
33 36
 })
... ...
@@ -38,15 +38,17 @@ runCxds <- function(inSCE,
38 38
     estNdbl = FALSE,
39 39
     useAssay = "counts") {
40 40
 
41
-    if (!is.null(sample)) {
42
-        if (length(sample) != ncol(inSCE)) {
43
-            stop("'sample' must be the same length as the number",
44
-                " of columns in 'inSCE'")
45
-        }
46
-    } else {
47
-        sample <- rep(1, ncol(inSCE))
48
-    }
49
-
41
+    #if (!is.null(sample)) {
42
+    #    if (length(sample) != ncol(inSCE)) {
43
+    #        stop("'sample' must be the same length as the number",
44
+    #            " of columns in 'inSCE'")
45
+    #    }
46
+    #} else {
47
+    #    sample <- rep(1, ncol(inSCE))
48
+    #}
49
+    if (!is.null(sample)) sample <- .manageCellVar(inSCE, var = sample)
50
+    else sample <- rep(1, ncol(inSCE))
51
+    
50 52
     message(paste0(date(), " ... Running 'cxds'"))
51 53
 
52 54
     ## Getting current arguments
... ...
@@ -160,14 +162,16 @@ runBcds <- function(inSCE,
160 162
     useAssay = "counts"
161 163
     ) {
162 164
 
163
-    if (!is.null(sample)) {
164
-        if (length(sample) != ncol(inSCE)) {
165
-            stop("'sample' must be the same length as the number",
166
-                " of columns in 'inSCE'")
167
-        }
168
-    } else {
169
-        sample <- rep(1, ncol(inSCE))
170
-    }
165
+    #if (!is.null(sample)) {
166
+    #    if (length(sample) != ncol(inSCE)) {
167
+    #        stop("'sample' must be the same length as the number",
168
+    #            " of columns in 'inSCE'")
169
+    #    }
170
+    #} else {
171
+    #    sample <- rep(1, ncol(inSCE))
172
+    #}
173
+    if (!is.null(sample)) sample <- .manageCellVar(inSCE, var = sample)
174
+    else sample <- rep(1, ncol(inSCE))
171 175
 
172 176
     message(paste0(date(), " ... Running 'bcds'"))
173 177
 
... ...
@@ -287,14 +291,16 @@ runCxdsBcdsHybrid <- function(inSCE,
287 291
     force = FALSE,
288 292
     useAssay = "counts") {
289 293
 
290
-    if (!is.null(sample)) {
291
-        if (length(sample) != ncol(inSCE)) {
292
-            stop("'sample' must be the same length as the number",
293
-                " of columns in 'inSCE'")
294
-        }
295
-    } else {
296
-        sample <- rep(1, ncol(inSCE))
297
-    }
294
+    #if (!is.null(sample)) {
295
+    #    if (length(sample) != ncol(inSCE)) {
296
+    #        stop("'sample' must be the same length as the number",
297
+    #            " of columns in 'inSCE'")
298
+    #    }
299
+    #} else {
300
+    #    sample <- rep(1, ncol(inSCE))
301
+    #}
302
+    if (!is.null(sample)) sample <- .manageCellVar(inSCE, var = sample)
303
+    else sample <- rep(1, ncol(inSCE))
298 304
 
299 305
     message(paste0(date(), " ... Running 'cxds_bcds_hybrid'"))
300 306
 
... ...
@@ -104,18 +104,16 @@ if (typeof(S4Vectors::metadata(sce.qc)$assayType) == 'list') {
104 104
   S4Vectors::metadata(sce.qc)$assayType <- assayType
105 105
 }
106 106
 
107
-sce.qc <- getUMAP(sce.qc, useAssay = "counts", reducedDimName = "QC_UMAP", sample = sceSample)
107
+sce.qc <- runQuickUMAP(sce.qc, reducedDimName = "QC_UMAP", sample = sceSample)
108 108
 
109 109
 if (is.null(reducedDimName)) {
110 110
   allSampleReducedDim <- "All_UMAP"
111
-  sce.qc <- getUMAP(sce.qc, useAssay = "counts", 
112
-                    reducedDimName = allSampleReducedDim, sample = NULL)
111
+  sce.qc <- runQuickUMAP(sce.qc, reducedDimName = allSampleReducedDim, sample = NULL)
113 112
 } else if (!reducedDimName %in% reducedDimNames(sce.qc)) {
114 113
   warning("'reducedDimName' not found in the reducedDimNames of the sce object. ",
115 114
   "Generate new reduced dimension reduction for all samples. ")
116 115
   allSampleReducedDim <- "All_UMAP"
117
-  sce.qc <- getUMAP(sce.qc, useAssay = "counts", 
118
-                    reducedDimName = allSampleReducedDim, sample = NULL)
116
+  sce.qc <- runQuickUMAP(sce.qc, reducedDimName = allSampleReducedDim, sample = NULL)
119 117
 } else {
120 118
   allSampleReducedDim <- reducedDimName
121 119
 }
... ...
@@ -592,3 +592,39 @@ dataAnnotationColor <- function(inSCE, axis = NULL,
592 592
     }
593 593
     return(allColorMap)
594 594
 }
595
+
596
+# Pass newly generated QC metric variable from vals$original to vals$counts, the
597
+# latter might be a subset.
598
+passQCVar <- function(sce.original, sce.counts, algoList) {
599
+  vars <- c()
600
+  for (a in algoList) {
601
+    if (a == "scDblFinder") {
602
+      new <- grep("scDblFinder", names(colData(sce.original)), value = TRUE)
603
+    } else if (a == "cxds") {
604
+      new <- grep("scds_cxds", names(colData(sce.original)), value = TRUE)
605
+    } else if (a == "bcds") {
606
+      new <- grep("scds_bcds", names(colData(sce.original)), value = TRUE)
607
+    } else if (a == "cxds_bcds_hybrid") {
608
+      new <- grep("scds_hybrid", names(colData(sce.original)), value = TRUE)
609
+    } else if (a == "decontX") {
610
+      new <- grep("decontX", names(colData(sce.original)), value = TRUE)
611
+    } else if (a == "soupX") {
612
+      new <- grep("soupX", names(colData(sce.original)), value = TRUE)
613
+    } else if (a == "scrublet") {
614
+      new <- grep("scrublet", names(colData(sce.original)), value = TRUE)
615
+    } else if (a == "doubletFinder") {
616
+      new <- grep("doubletFinder", names(colData(sce.original)), value = TRUE)
617
+    } else if (a == "QCMetrics") {
618
+      new <- c("total", "sum", "detected")
619
+      new <- c(new, grep("percent.top", names(colData(sce.original)), value = TRUE))
620
+      new <- c(new, grep("mito_", names(colData(sce.original)), value = TRUE))
621
+      new <- c(new, grep("^subsets_.+_sum$", names(colData(sce.original)), value = TRUE))
622
+      new <- c(new, grep("^subsets_.+_detected$", names(colData(sce.original)), value = TRUE))
623
+      new <- c(new, grep("^subsets_.+_percent$", names(colData(sce.original)), value = TRUE))
624
+    } 
625
+    vars <- c(vars, new)
626
+  }
627
+  sce.original <- sce.original[rownames(sce.counts), colnames(sce.counts)]
628
+  colData(sce.counts)[vars] <- colData(sce.original)[vars]
629
+  return(sce.counts)
630
+}
... ...
@@ -227,10 +227,12 @@ shinyServer(function(input, output, session) {
227 227
   }
228 228
 
229 229
 
230
-  updateSelectInputTag <- function(session, inputId, choices = NULL, selected = NULL,
231
-                                   label = "Select assay:", tags = NULL, recommended = NULL, showTags = TRUE,
232
-                                   redDims = FALSE){
233
-    choices <- expTaggedData(vals$counts, tags, redDims = redDims, showTags = showTags, recommended = recommended)
230
+  updateSelectInputTag <- function(session, inputId, choices = NULL, 
231
+                                   selected = NULL, label = "Select assay:", 
232
+                                   tags = NULL, recommended = NULL, 
233
+                                   showTags = TRUE, redDims = FALSE, 
234
+                                   inSCE = vals$counts){
235
+    choices <- expTaggedData(inSCE, tags, redDims = redDims, showTags = showTags, recommended = recommended)
234 236
     updateSelectizeInput(session = session, inputId = inputId, label = label, choices = choices, selected = selected)
235 237
   }
236 238
 
... ...
@@ -294,7 +296,7 @@ shinyServer(function(input, output, session) {
294 296
                            recommended = c("transformed", "normalized"))
295 297
     }
296 298
     updateSelectInputTag(session, "filterAssaySelect", choices = currassays)
297
-    updateSelectInputTag(session, "qcAssaySelect", recommended = "raw")
299
+    updateSelectInputTag(session, "qcAssaySelect", recommended = "raw", inSCE = vals$original)
298 300
     updateSelectInputTag(session, "celdaAssay", choices = currassays)
299 301
     updateSelectInputTag(session, "celdaAssayGS", choices = currassays)
300 302
     updateSelectInputTag(session, "celdaAssaytSNE", choices = currassays)
... ...
@@ -1735,12 +1737,12 @@ shinyServer(function(input, output, session) {
1735 1737
 
1736 1738
   updateQCPlots <- function() {
1737 1739
     # get selected sample from run QC section
1738
-    if (!is.null(vals$counts)) {
1740
+    if (!is.null(vals$original)) {
1739 1741
       qcSample <- input$qcSampleSelect
1740 1742
       if (qcSample == "None") {
1741 1743
         qcSample <- NULL
1742 1744
       } else {
1743
-        qcSample <- colData(vals$counts)[,input$qcSampleSelect]
1745
+        qcSample <- colData(vals$original)[,input$qcSampleSelect]
1744 1746
       }
1745 1747
       # build list of selected algos
1746 1748
       algoList = list()
... ...
@@ -1749,16 +1751,16 @@ shinyServer(function(input, output, session) {
1749 1751
           algoList <- c(algoList, algo)
1750 1752
         }
1751 1753
       }
1752
-      # only run getUMAP if there are no reducedDimNames
1754
+      # only run runUMAP if there are no reducedDimNames
1753 1755
       # redDimName <- input$qcPlotRedDim
1754 1756
       # show the tabs for the result plots  output[[qc_plot_ids[[a]]]]
1755 1757
 
1756 1758
       showQCResTabs(vals, algoList, qc_algo_status, qc_plot_ids)
1757
-      arrangeQCPlots(vals$counts, input, output, algoList,
1758
-                     colData(vals$counts)[[input$qcSampleSelect]], qc_plot_ids,
1759
+      arrangeQCPlots(vals$original, input, output, algoList,
1760
+                     colData(vals$original)[[input$qcSampleSelect]], qc_plot_ids,
1759 1761
                      qc_algo_status, input$QCUMAPName)
1760 1762
 
1761
-      uniqueSampleNames = unique(colData(vals$counts)[[input$qcSampleSelect]])
1763
+      uniqueSampleNames = unique(colData(vals$original)[[input$qcSampleSelect]])
1762 1764
       for (algo in algoList) {
1763 1765
         qc_algo_status[[algo]] <- list(self="done")
1764 1766
         if (length(uniqueSampleNames) > 1) {
... ...
@@ -1778,7 +1780,7 @@ shinyServer(function(input, output, session) {
1778 1780
           selector = "#qcPageErrors",
1779 1781
           ui = wellPanel(id = "noSelected", tags$b("Please select at least one algorithm.", style = "color: red;"))
1780 1782
         )
1781
-      } else if (is.null(vals$counts)) {
1783
+      } else if (is.null(vals$original)) {
1782 1784
         insertUI(
1783 1785
           selector = "#qcPageErrors",
1784 1786
           ui = wellPanel(id = "noSCE", tags$b("Please upload a sample first.", style = "color: red;"))
... ...
@@ -1868,7 +1870,7 @@ shinyServer(function(input, output, session) {
1868 1870
           }
1869 1871
         }
1870 1872
         # run selected cell QC algorithms
1871
-        vals$counts <- runCellQC(inSCE = vals$counts,
1873
+        vals$original <- runCellQC(inSCE = vals$original,
1872 1874
                                  algorithms = algoList,
1873 1875
                                  sample = qcSample,
1874 1876
                                  collectionName = qcCollName,
... ...
@@ -1877,27 +1879,31 @@ shinyServer(function(input, output, session) {
1877 1879
                                  mitoGeneLocation = mgsLoc,
1878 1880
                                  useAssay = input$qcAssaySelect,
1879 1881
                                  paramsList = paramsList)
1882
+        # Only copy the newly generated colData variables to vals$counts, but
1883
+        # not replacing the vals$counts. vals$counts might have already become
1884
+        # a subset.
1885
+        vals$counts <- passQCVar(vals$original, vals$counts, algoList)
1880 1886
         updateColDataNames()
1881 1887
         updateAssayInputs()
1882
-        # redDimList <- strsplit(reducedDimNames(vals$counts), " ")
1883
-        # run getUMAP if doublet/ambient RNA detection conducted
1888
+        # redDimList <- strsplit(reducedDimNames(vals$original), " ")
1889
+        # run runUMAP if doublet/ambient RNA detection conducted
1884 1890
         #umap generated during soupX, skip for now
1885
-        if(length(intersect(c("scDblFinder", "cxds", "bcds",
1891
+        if (length(intersect(c("scDblFinder", "cxds", "bcds",
1886 1892
              "cxds_bcds_hybrid", "decontX", #"soupX",
1887
-             "scrublet", "doubletFinder"), algoList))){
1893
+             "scrublet", "doubletFinder"), algoList)) > 0) {
1888 1894
           message(paste0(date(), " ... Running 'UMAP'"))
1889
-          vals$counts <- getUMAP(inSCE = vals$counts,
1890
-                                 sample = qcSample,
1891
-                                 useAssay = input$qcAssaySelect,
1892
-                                 nNeighbors = input$UnNeighbors,
1893
-                                 nIterations = input$UnIterations,
1894
-                                 alpha = input$Ualpha,
1895
-                                 minDist = input$UminDist,
1896
-                                 spread = input$Uspread,
1897
-                                 initialDims = input$UinitialDims,
1898
-                                 reducedDimName = input$QCUMAPName,
1899
-                                 seed = input$Useed
1900
-                                 )
1895
+          vals$original <- runUMAP(inSCE = vals$original,
1896
+                                   sample = qcSample,
1897
+                                   useAssay = input$qcAssaySelect,
1898
+                                   useReducedDim = NULL,
1899
+                                   nNeighbors = input$UnNeighbors,
1900
+                                   nIterations = input$UnIterations,
1901
+                                   alpha = input$Ualpha,
1902
+                                   minDist = input$UminDist,
1903
+                                   spread = input$Uspread,
1904
+                                   initialDims = input$UinitialDims,
1905
+                                   reducedDimName = input$QCUMAPName,
1906
+                                   seed = input$Useed)
1901 1907
 
1902 1908
         }
1903 1909
         message(paste0(date(), " ... QC Complete"))
... ...
@@ -1920,15 +1926,15 @@ shinyServer(function(input, output, session) {
1920 1926
   rowFilteringParams <- reactiveValues(params = list(), id_count = 0)
1921 1927
 
1922 1928
   observeEvent(input$addFilteringParam, {
1923
-    if (!is.null(vals$counts)) {
1924
-      showModal(filteringModal(colNames = names(colData(vals$counts))))
1929
+    if (!is.null(vals$original)) {
1930
+      showModal(filteringModal(colNames = names(colData(vals$original))))
1925 1931
     }
1926 1932
   })
1927 1933
 
1928 1934
   observeEvent(input$addRowFilteringParam, {
1929
-    if (!is.null(vals$counts) &&
1930
-        !is.null(names(assays(vals$counts)))) {
1931
-      showModal(rowFilteringModal(assayInput = names(assays(vals$counts))))
1935
+    if (!is.null(vals$original) &&
1936
+        !is.null(names(assays(vals$original)))) {
1937
+      showModal(rowFilteringModal(assayInput = names(assays(vals$original))))
1932 1938
     }
1933 1939
   })
1934 1940
 
... ...
@@ -1938,13 +1944,13 @@ shinyServer(function(input, output, session) {
1938 1944
     removeUI(selector = "#newThresh")
1939 1945
     removeUI(selector = "div:has(>> #convertToCat)")
1940 1946
     # check if column contains numerical values
1941
-    isNum <- is.numeric(vals$counts[[input$filterColSelect]][0])
1942
-    if (length(vals$counts[[input$filterColSelect]]) > 0) {
1947
+    isNum <- is.numeric(vals$original[[input$filterColSelect]][0])
1948
+    if (length(vals$original[[input$filterColSelect]]) > 0) {
1943 1949
       if (isTRUE(isNum)) {
1944 1950
         # (from partials) insertUI for choosing greater than and less than params
1945
-        addFilteringThresholdOptions(vals$counts[[input$filterColSelect]])
1951
+        addFilteringThresholdOptions(vals$original[[input$filterColSelect]])
1946 1952
         # if less than 25 unique categories, give categorical option
1947
-        if (length(unique(vals$counts[[input$filterColSelect]])) < 25) {
1953
+        if (length(unique(vals$original[[input$filterColSelect]])) < 25) {
1948 1954
           insertUI(
1949 1955
             selector = "#convertFilterType",
1950 1956
             ui = checkboxInput("convertToCat", "Convert to categorical filter?")
... ...
@@ -1957,7 +1963,7 @@ shinyServer(function(input, output, session) {
1957 1963
           selector = "#filterCriteria",
1958 1964
           ui = tags$div(id="newThresh",
1959 1965
                         checkboxGroupInput("filterThresh", "Please select which columns to keep:",
1960
-                                           choices = as.vector(unique(vals$counts[[input$filterColSelect]])),
1966
+                                           choices = as.vector(unique(vals$original[[input$filterColSelect]])),
1961 1967
                         ),
1962 1968
           )
1963 1969
         )
... ...
@@ -1978,13 +1984,13 @@ shinyServer(function(input, output, session) {
1978 1984
           selector = "#filterCriteria",
1979 1985
           ui = tags$div(id="newThresh",
1980 1986
                         checkboxGroupInput("filterThresh", "Please select which columns to keep:",
1981
-                                           choices = as.vector(unique(vals$counts[[input$filterColSelect]])),
1987
+                                           choices = as.vector(unique(vals$original[[input$filterColSelect]])),
1982 1988
                         )
1983 1989
           )
1984 1990
         )
1985 1991
       } else {
1986
-        addFilteringThresholdOptions(vals$counts[[input$filterColSelect]])
1987
-        if (length(unique(vals$counts[[input$filterColSelect]])) < 25) {
1992
+        addFilteringThresholdOptions(vals$original[[input$filterColSelect]])
1993
+        if (length(unique(vals$original[[input$filterColSelect]])) < 25) {
1988 1994
           shinyjs::show("convertFilterType")
1989 1995
         }
1990 1996
       }
... ...
@@ -2005,7 +2011,7 @@ shinyServer(function(input, output, session) {
2005 2011
 
2006 2012
   observeEvent(input$filtModalOK, {
2007 2013
     if (is.null(input$filterThresh) && is.null(input$filterThreshGT) && is.null(input$filterThreshLT)) {
2008
-      showModal(filteringModal(failed=TRUE, colNames = names(colData(vals$counts))))
2014
+      showModal(filteringModal(failed=TRUE, colNames = names(colData(vals$original))))
2009 2015
     } else {
2010 2016
       id <- paste0("filteringParam", filteringParams$id_count)
2011 2017
       # figure out which options the user selected
... ...
@@ -2073,7 +2079,7 @@ shinyServer(function(input, output, session) {
2073 2079
 
2074 2080
   observeEvent(input$rowFiltModalOK, {
2075 2081
     if ((is.null(input$filterThreshX)) || (is.null(input$filterThreshY)) || (is.null(input$filterAssaySelect))) {
2076
-      showModal(rowFilteringModal(failed=TRUE, assayInput = names(assays(vals$counts))))
2082
+      showModal(rowFilteringModal(failed=TRUE, assayInput = names(assays(vals$original))))
2077 2083
     } else {
2078 2084
       id <- paste0("rowFilteringParam", rowFilteringParams$id_count)
2079 2085
       # new row in parameters table
... ...
@@ -2112,29 +2118,43 @@ shinyServer(function(input, output, session) {
2112 2118
     }
2113 2119
     rowFilteringParams$params <- list()
2114 2120
   })
2115
-
2116
-  observeEvent(input$filterSCE, withConsoleMsgRedirect(
2117
-    msg = "Please wait while data is being filtered. See console log for progress.",
2118
-    {
2121
+  
2122
+  filterSCE <- function(inSCE, colFilter, rowFilter) {
2123
+    if (!is.null(colFilter)) {
2119 2124
       # handle column filtering (pull out the criteria strings first)
2120
-      colInput <- formatFilteringCriteria(filteringParams$params)
2125
+      colInput <- formatFilteringCriteria(colFilter$params)
2121 2126
       if (length(colInput) > 0) {
2122
-        vals$counts <- subsetSCECols(vals$counts, colData = colInput)
2127
+        inSCE <- subsetSCECols(inSCE, colData = colInput)
2123 2128
       }
2124
-
2125
-      # handle row filtering (enter information as rows first, then pull out criteria strings)
2126
-      vals$counts <- addRowFiltersToSCE(vals$counts, rowFilteringParams)
2127
-      rowInput <- formatFilteringCriteria(rowFilteringParams$params)
2129
+    }
2130
+    if (!is.null(rowFilter)) {
2131
+      # handle row filtering (enter information as rows first, then pull out 
2132
+      # criteria strings)
2133
+      rowInput <- formatFilteringCriteria(rowFilter$params)
2128 2134
       if (length(rowInput) > 0) {
2129
-        temp <- subsetSCERows(vals$counts, rowData = rowInput, returnAsAltExp = FALSE)
2135
+        inSCE <- addRowFiltersToSCE(inSCE, rowFilter)
2136
+        temp <- subsetSCERows(inSCE, rowData = rowInput, returnAsAltExp = FALSE)
2130 2137
         if (nrow(temp) == 0) {
2131 2138
           stop("This filter will clear all rows. Filter has not been applied.")
2132 2139
         } else {
2133
-          vals$counts <- temp
2140
+          inSCE <- temp
2134 2141
         }
2135 2142
       }
2143
+    }
2144
+    return(inSCE)
2145
+  }
2146
+  
2147
+  observeEvent(input$filterSCE, withConsoleMsgRedirect(
2148
+    msg = "Please wait while data is being filtered. See console log for progress.",
2149
+    {
2150
+      vals$counts <- filterSCE(vals$original, filteringParams, rowFilteringParams)
2136 2151
       shinyjs::show(id="filteringSummary")
2137
-
2152
+      updateColDataNames()
2153
+      updateReddimInputs()
2154
+      updateFeatureAnnots()
2155
+      updateAssayInputs()
2156
+      # TODO: When new subset is being created and maybe replacing previous
2157
+      # vals$counts, please find if any of the downstream UI need to be updated
2138 2158
       # Show downstream analysis options
2139 2159
       shinyjs::show(selector = ".nlw-qcf")
2140 2160
   }))
... ...
@@ -2,12 +2,18 @@
2 2
 % Please edit documentation in R/allGenerics.R, R/sampleSummaryStats.R
3 3
 \name{getSampleSummaryStatsTable}
4 4
 \alias{getSampleSummaryStatsTable}
5
+\alias{setSampleSummaryStatsTable<-}
5 6
 \alias{getSampleSummaryStatsTable,SingleCellExperiment-method}
7
+\alias{setSampleSummaryStatsTable<-,SingleCellExperiment-method}
6 8
 \title{Stores and returns table of SCTK QC outputs to metadata.}
7 9
 \usage{
8 10
 getSampleSummaryStatsTable(inSCE, statsName, ...)
9 11
 
12
+setSampleSummaryStatsTable(inSCE, statsName, ...) <- value
13
+
10 14
 \S4method{getSampleSummaryStatsTable}{SingleCellExperiment}(inSCE, statsName, ...)
15
+
16
+\S4method{setSampleSummaryStatsTable}{SingleCellExperiment}(inSCE, statsName, ...) <- value
11 17
 }
12 18
 \arguments{
13 19
 \item{inSCE}{Input \linkS4class{SingleCellExperiment} object with saved
... ...
@@ -18,10 +24,15 @@ that stores the stats table within the metadata of the
18 24
 SingleCellExperiment object. Required.}
19 25
 
20 26
 \item{...}{Other arguments passed to the function.}
27
+
28
+\item{value}{The summary table for QC statistics generated from SingleCellTK
29
+to be added to the SCE object.}
21 30
 }
22 31
 \value{
23
-A matrix/array object. Contains a summary table for QC statistics
24
-generated from SingleCellTK.
32
+For \code{getSampleSummaryStatsTable}, A matrix/array object. 
33
+Contains a summary table for QC statistics generated from SingleCellTK. For
34
+\code{setSampleSummaryStatsTable<-}, A SingleCellExperiment object where the 
35
+summary table is updated in the \code{metadata} slot.
25 36
 }
26 37
 \description{
27 38
 Stores and returns table of QC metrics generated from
... ...
@@ -144,8 +144,7 @@ A wrapper function which visualizes outputs from the
144 144
 \examples{
145 145
 data(scExample, package="singleCellTK")
146 146
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
147
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
148
-               reducedDimName="UMAP")
147
+sce <- runQuickUMAP(sce)
149 148
 sce <- runBcds(sce)
150 149
 plotBcdsResults(inSCE=sce, reducedDimName="UMAP")
151 150
 }
... ...
@@ -144,8 +144,7 @@ A wrapper function which visualizes outputs from the
144 144
 \examples{
145 145
 data(scExample, package="singleCellTK")
146 146
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
147
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
148
-               reducedDimName="UMAP")
147
+sce <- runQuickUMAP(sce)
149 148
 sce <- runCxds(sce)
150 149
 plotCxdsResults(inSCE=sce, reducedDimName="UMAP")
151 150
 }
... ...
@@ -144,8 +144,7 @@ A wrapper function which visualizes outputs from the
144 144
 \examples{
145 145
 data(scExample, package="singleCellTK")
146 146
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
147
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
148
-               reducedDimName="UMAP")
147
+sce <- runQuickUMAP(sce)
149 148
 sce <- runDoubletFinder(sce)
150 149
 plotDoubletFinderResults(inSCE=sce, reducedDimName="UMAP")
151 150
 }
... ...
@@ -144,8 +144,7 @@ A wrapper function which visualizes outputs from the
144 144
 \examples{
145 145
 data(scExample, package="singleCellTK")
146 146
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
147
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
148
-               reducedDimName="UMAP")
147
+sce <- runQuickUMAP(sce)
149 148
 sce <- runScDblFinder(sce)
150 149
 plotScDblFinderResults(inSCE=sce, reducedDimName="UMAP")
151 150
 }
... ...
@@ -144,8 +144,7 @@ A wrapper function which visualizes outputs from the
144 144
 \examples{
145 145
 data(scExample, package="singleCellTK")
146 146
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
147
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
148
-               reducedDimName="UMAP")
147
+sce <- runQuickUMAP(sce)
149 148
 sce <- runCxdsBcdsHybrid(sce)
150 149
 plotScdsHybridResults(inSCE=sce, reducedDimName="UMAP")
151 150
 }
... ...
@@ -145,8 +145,7 @@ A wrapper function which visualizes outputs from the
145 145
 data(scExample, package="singleCellTK")
146 146
 \dontrun{
147 147
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
148
-sce <- getUMAP(inSCE=sce, useAssay="counts", logNorm=TRUE, 
149
-               reducedDimName="UMAP")
148
+sce <- runQuickUMAP(sce)
150 149
 sce <- runScrublet(sce)
151 150
 plotScrubletResults(inSCE=sce, reducedDimName="UMAP")
152 151
 }
... ...
@@ -10,7 +10,7 @@ plotTSNE(
10 10
   shape = NULL,
11 11
   reducedDimName = "TSNE",
12 12
   runTSNE = FALSE,
13
-  useAssay = "logcounts"
13
+  useAssay = "counts"
14 14
 )
15 15
 }
16 16
 \arguments{
... ...
@@ -10,7 +10,7 @@ plotUMAP(
10 10
   shape = NULL,
11 11
   reducedDimName = "UMAP",
12 12
   runUMAP = FALSE,
13
-  useAssay = "logcounts"
13
+  useAssay = "counts"
14 14
 )
15 15
 }
16 16
 \arguments{
... ...
@@ -38,6 +38,6 @@ Plot UMAP results either on already run results or run first and then plot.
38 38
 \examples{
39 39
 data(scExample, package = "singleCellTK")
40 40
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
41
-sce <- getUMAP(inSCE = sce, useAssay = "counts", reducedDimName = "UMAP")
41
+sce <- runQuickUMAP(sce)
42 42
 plotUMAP(sce)
43 43
 }
... ...
@@ -35,7 +35,7 @@ data(scExample, package = "singleCellTK")
35 35
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
36 36
 \dontrun{
37 37
 sce <- runDecontX(sce)
38
-sce <- getUMAP(sce, useAssay = "counts", logNorm = TRUE)
38
+sce <- runQuickUMAP(sce)
39 39
 reportQCTool(inSCE = sce, algorithm = "DecontX")
40 40
 }
41 41
 }
... ...
@@ -66,8 +66,8 @@ Generic Wrapper function for running dimensionality reduction
66 66
 \details{
67 67
 Wrapper function to run one of the available dimensionality
68 68
 reduction algorithms integrated within SCTK from \code{\link{scaterPCA}},
69
-\code{\link{runSeuratPCA}}, \code{\link{runSeuratICA}}, \code{\link{getTSNE}},
70
-\code{\link{runSeuratTSNE}}, \code{\link{getUMAP}} and
69
+\code{\link{runSeuratPCA}}, \code{\link{runSeuratICA}}, \code{\link{runTSNE}},
70
+\code{\link{runSeuratTSNE}}, \code{\link{runUMAP}} and
71 71
 \code{\link{runSeuratUMAP}}. Users can use an assay by specifying
72 72
 \code{useAssay}, use the assay in an altExp by specifying both
73 73
 \code{useAltExp} and \code{useAssay}, or use a low-dimensionality
74 74
similarity index 80%
75 75
rename from man/getTSNE.Rd
76 76
rename to man/runTSNE.Rd
... ...
@@ -1,16 +1,41 @@
1 1
 % Generated by roxygen2: do not edit by hand
2
-% Please edit documentation in R/getTSNE.R
3
-\name{getTSNE}
2
+% Please edit documentation in R/runTSNE.R
3
+\name{runTSNE}
4
+\alias{runTSNE}
5
+\alias{runQuickTSNE}
4 6
 \alias{getTSNE}
5 7
 \title{Run t-SNE embedding with Rtsne method}
6 8
 \usage{
9
+runTSNE(
10
+  inSCE,
11
+  useReducedDim = "PCA",
12
+  useAssay = NULL,
13
+  useAltExp = NULL,
14
+  reducedDimName = "TSNE",
15
+  logNorm = TRUE,
16
+  useFeatureSubset = NULL,
17
+  nTop = 2000,
18
+  center = TRUE,
19
+  scale = TRUE,
20
+  pca = TRUE,
21
+  partialPCA = FALSE,
22
+  initialDims = 25,
23
+  theta = 0.5,
24
+  perplexity = 30,
25
+  nIterations = 1000,
26
+  numThreads = 1,
27
+  seed = NULL
28
+)
29
+
30
+runQuickTSNE(inSCE, useAssay = "counts", ...)
31
+
7 32
 getTSNE(
8 33
   inSCE,
9
-  useAssay = "logcounts",
10
-  useReducedDim = NULL,
34
+  useReducedDim = "PCA",
35
+  useAssay = NULL,
11 36
   useAltExp = NULL,
12 37
   reducedDimName = "TSNE",
13
-  logNorm = FALSE,
38
+  logNorm = TRUE,
14 39
   useFeatureSubset = NULL,
15 40
   nTop = 2000,
16 41
   center = TRUE,
... ...
@@ -28,12 +53,12 @@ getTSNE(
28 53
 \arguments{
29 54
 \item{inSCE}{Input \linkS4class{SingleCellExperiment} object.}
30 55
 
56
+\item{useReducedDim}{The low dimension representation to use for UMAP
57
+computation. Default \code{"PCA"}.}
58
+
31 59
 \item{useAssay}{Assay to use for tSNE computation. If \code{useAltExp} is
32 60
 specified, \code{useAssay} has to exist in
33
-\code{assays(altExp(inSCE, useAltExp))}. Default \code{"logcounts"}.}
34
-
35
-\item{useReducedDim}{The low dimension representation to use for UMAP
36
-computation. Default \code{NULL}.}
61
+\code{assays(altExp(inSCE, useAltExp))}. Default \code{NULL}.}
37 62
 
38 63
 \item{useAltExp}{The subset to use for tSNE computation, usually for the
39 64
 selected.variable features. Default \code{NULL}.}
... ...
@@ -43,7 +68,7 @@ reductions. Default \code{"TSNE"}.}
43 68
 
44 69
 \item{logNorm}{Whether the counts will need to be log-normalized prior to
45 70
 generating the tSNE via \code{\link{scaterlogNormCounts}}. Ignored when using
46
-\code{useReducedDim}. Default \code{FALSE}.}
71
+\code{useReducedDim}. Default \code{TRUE}.}
47 72
 
48 73
 \item{useFeatureSubset}{Subset of feature to use for dimension reduction. A
49 74
 character string indicating a \code{rowData} variable that stores the logical
... ...
@@ -84,6 +109,8 @@ accuracy), set to \code{0.0} for exact TSNE. Default \code{0.5}.}
84 109
 
85 110
 \item{seed}{Random seed for reproducibility of tSNE results.
86 111
 Default \code{NULL} will use global seed in use by the R environment.}
112
+
113
+\item{...}{Other parameters to be passed to \code{runTSNE}}
87 114
 }
88 115
 \value{
89 116
 A \linkS4class{SingleCellExperiment} object with tSNE computation
... ...
@@ -104,14 +131,15 @@ input PCA, and will be much faster.
104 131
 data(scExample, package = "singleCellTK")
105 132
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
106 133
 # Run from raw counts
107
-sce <- getTSNE(inSCE = sce, useAssay = "counts", logNorm = TRUE, nTop = 2000,
108
-               scale = TRUE, pca = TRUE)
134
+sce <- runQuickTSNE(sce)
109 135
 \dontrun{
110 136
 # Run from PCA
111 137
 sce <- scaterlogNormCounts(sce, "logcounts")
112 138
 sce <- runModelGeneVar(sce)
139
+sce <- setTopHVG(sce, method = "modelGeneVar", hvgNumber = 2000, 
140
+                 featureSubsetName = "HVG_modelGeneVar2000")
113 141
 sce <- scaterPCA(sce, useAssay = "logcounts",
114 142
                  useFeatureSubset = "HVG_modelGeneVar2000", scale = TRUE)
115
-sce <- getTSNE(sce, useReducedDim = "PCA")
143
+sce <- runTSNE(sce, useReducedDim = "PCA")
116 144
 }
117 145
 }
118 146
similarity index 73%
119 147
rename from man/getUMAP.Rd
120 148
rename to man/runUMAP.Rd
... ...
@@ -1,17 +1,43 @@
1 1
 % Generated by roxygen2: do not edit by hand
2
-% Please edit documentation in R/getUMAP.R
3
-\name{getUMAP}
2
+% Please edit documentation in R/runUMAP.R
3
+\name{runUMAP}
4
+\alias{runUMAP}
5
+\alias{runQuickUMAP}
4 6
 \alias{getUMAP}
5 7
 \title{Run UMAP embedding with scater method}
6 8
 \usage{
9
+runUMAP(
10
+  inSCE,
11
+  useReducedDim = "PCA",
12
+  useAssay = NULL,
13
+  useAltExp = NULL,
14
+  sample = NULL,
15
+  reducedDimName = "UMAP",
16
+  logNorm = TRUE,
17
+  useFeatureSubset = NULL,
18
+  nTop = 2000,
19
+  scale = TRUE,
20
+  pca = TRUE,
21
+  initialDims = 25,
22
+  nNeighbors = 30,
23
+  nIterations = 200,
24
+  alpha = 1,
25
+  minDist = 0.01,
26
+  spread = 1,
27
+  seed = NULL,
28
+  BPPARAM = SerialParam()
29
+)
30
+
31
+runQuickUMAP(inSCE, useAssay = "counts", sample = "sample", ...)
32
+
7 33
 getUMAP(
8 34
   inSCE,
9
-  useAssay = "logcounts",
10
-  useReducedDim = NULL,
35
+  useReducedDim = "PCA",
36
+  useAssay = NULL,
11 37
   useAltExp = NULL,
12 38
   sample = NULL,
13 39
   reducedDimName = "UMAP",
14
-  logNorm = FALSE,
40
+  logNorm = TRUE,
15 41
   useFeatureSubset = NULL,
16 42
   nTop = 2000,
17 43
   scale = TRUE,
... ...
@@ -23,20 +49,20 @@ getUMAP(
23 49
   minDist = 0.01,
24 50
   spread = 1,
25 51
   seed = NULL,
26
-  BPPARAM = BiocParallel::SerialParam()
52
+  BPPARAM = SerialParam()
27 53
 )
28 54
 }
29 55
 \arguments{
30 56
 \item{inSCE}{Input \linkS4class{SingleCellExperiment} object.}
31 57
 
58
+\item{useReducedDim}{The low dimension representation to use for UMAP
59
+computation. If \code{useAltExp} is specified, \code{useReducedDim} has to
60
+exist in \code{reducedDims(altExp(inSCE, useAltExp))}. Default \code{"PCA"}.}
61
+
32 62
 \item{useAssay}{Assay to use for UMAP computation. If \code{useAltExp} is
33 63
 specified, \code{useAssay} has to exist in
34 64
 \code{assays(altExp(inSCE, useAltExp))}. Ignored when using
35
-\code{useReducedDim}. Default \code{"logcounts"}.}
36
-
37
-\item{useReducedDim}{The low dimension representation to use for UMAP
38
-computation. If \code{useAltExp} is specified, \code{useReducedDim} has to
39
-exist in \code{reducedDims(altExp(inSCE, useAltExp))}. Default \code{NULL}.}
65
+\code{useReducedDim}. Default \code{NULL}.}
40 66
 
41 67
 \item{useAltExp}{The subset to use for UMAP computation, usually for the
42 68
 selected variable features. Default \code{NULL}.}
... ...
@@ -50,7 +76,7 @@ coordinates obtained from this method. Default \code{"UMAP"}.}
50 76
 
51 77
 \item{logNorm}{Whether the counts will need to be log-normalized prior to
52 78
 generating the UMAP via \code{\link{scaterlogNormCounts}}. Ignored when using
53
-\code{useReducedDim}. Default \code{FALSE}.}
79
+\code{useReducedDim}. Default \code{TRUE}.}
54 80
 
55 81
 \item{useFeatureSubset}{Subset of feature to use for dimension reduction. A
56 82
 character string indicating a \code{rowData} variable that stores the logical
... ...
@@ -97,6 +123,8 @@ Default \code{NULL} will use global seed in use by the R environment.}
97 123
 
98 124
 \item{BPPARAM}{A \linkS4class{BiocParallelParam} object specifying whether
99 125
 the PCA should be parallelized.}
126
+
127
+\item{...}{Parameters passed to \code{runUMAP}}
100 128
 }
101 129
 \value{
102 130
 A \linkS4class{SingleCellExperiment} object with UMAP computation
... ...
@@ -104,27 +132,30 @@ updated in \code{reducedDim(inSCE, reducedDimName)}.
104 132
 }
105 133
 \description{
106 134
 Uniform Manifold Approximation and Projection (UMAP) algorithm
107
-is commonly for 2D visualization of single-cell data. This function wraps the
108
-scater \code{\link[scater]{calculateUMAP}} function.
109
-
110
-With this funciton, users can create UMAP embedding directly from raw count
111
-matrix, with necessary preprocessing including normalization, scaling,
112
-dimension reduction all automated. Yet we still recommend having the PCA as
113
-input, so that the result can match with the clustering based on the same
114
-input PCA.
135
+is commonly for 2D visualization of single-cell data. These functions wrap 
136
+the scater \code{\link[scater]{calculateUMAP}} function.
137
+
138
+Users can use \code{runQuickUMAP} to directly create UMAP embedding from raw
139
+count matrix, with necessary preprocessing including normalization, variable
140
+feature selection, scaling, dimension reduction all automated. Therefore, 
141
+\code{useReducedDim} is disabled for \code{runQuickUMAP}. 
142
+
143
+In a complete analysis, we still recommend having dimension reduction such as
144
+PCA created beforehand and select proper numbers of dimensions for using
145
+\code{runUMAP}, so that the result can match with the clustering based on the
146
+same input PCA.
115 147
 }
116 148
 \examples{
117 149
 data(scExample, package = "singleCellTK")
118 150
 sce <- subsetSCECols(sce, colData = "type != 'EmptyDroplet'")
119 151
 # Run from raw counts
120
-sce <- getUMAP(inSCE = sce, useAssay = "counts", logNorm = TRUE, nTop = 2000,
121
-               scale = TRUE, pca = TRUE)
152
+sce <- runQuickUMAP(sce)
122 153
 \dontrun{
123 154
 # Run from PCA
124 155
 sce <- scaterlogNormCounts(sce, "logcounts")
125 156
 sce <- runModelGeneVar(sce)
126 157
 sce <- scaterPCA(sce, useAssay = "logcounts",
127 158
                  useFeatureSubset = "HVG_modelGeneVar2000", scale = TRUE)
128
-sce <- getUMAP(sce, useReduc