... | ... |
@@ -100,20 +100,16 @@ |
100 | 100 |
#' @importFrom BiocGenerics sizeFactors sizeFactors<- cbind |
101 | 101 |
#' @importFrom scuttle logNormCounts librarySizeFactors .unpackLists |
102 | 102 |
#' @importFrom SingleCellExperiment altExp altExp<- |
103 |
-multiBatchNorm <- function(..., batch=NULL, assay.type="counts", norm.args=list(), as.altexp=NULL, |
|
104 |
- min.mean=1, subset.row=NULL, normalize.all=FALSE, preserve.single=TRUE, BPPARAM=SerialParam()) |
|
103 |
+multiBatchNorm <- function(..., batch=NULL, norm.args=list(), |
|
104 |
+ min.mean=1, subset.row=NULL, normalize.all=FALSE, preserve.single=TRUE, |
|
105 |
+ assay.type="counts", as.altexp=NULL, BPPARAM=SerialParam()) |
|
105 | 106 |
{ |
106 | 107 |
batches <- .unpackLists(...) |
107 |
- checkBatchConsistency(batches) |
|
108 |
- if (length(batches)==0L) { |
|
109 |
- stop("at least one SingleCellExperiment must be supplied") |
|
110 |
- } |
|
111 |
- |
|
112 |
- # Setting up the parallelization environment. |
|
113 |
- if (.bpNotSharedOrUp(BPPARAM)) { |
|
114 |
- bpstart(BPPARAM) |
|
115 |
- on.exit(bpstop(BPPARAM), add=TRUE) |
|
108 |
+ if (!is.null(as.altexp)) { |
|
109 |
+ originals <- batches |
|
110 |
+ batches <- lapply(batches, altExp, e=as.altexp) |
|
116 | 111 |
} |
112 |
+ checkBatchConsistency(batches) |
|
117 | 113 |
|
118 | 114 |
# Handling the batch= and preserve.single= options. |
119 | 115 |
if (length(batches)==1L) { |
... | ... |
@@ -122,20 +118,30 @@ multiBatchNorm <- function(..., batch=NULL, assay.type="counts", norm.args=list( |
122 | 118 |
} |
123 | 119 |
|
124 | 120 |
if (!preserve.single) { |
125 |
- sce <- batches[[1]] |
|
126 | 121 |
by.batch <- split(seq_along(batch), batch) |
127 |
- batches <- by.batch |
|
128 |
- for (i in seq_along(by.batch)) { |
|
129 |
- batches[[i]] <- sce[,by.batch[[i]],drop=FALSE] |
|
122 |
+ FRAGMENT <- function(target) { |
|
123 |
+ batches <- by.batch |
|
124 |
+ for (i in seq_along(by.batch)) { |
|
125 |
+ batches[[i]] <- target[,by.batch[[i]],drop=FALSE] |
|
126 |
+ } |
|
127 |
+ batches |
|
128 |
+ } |
|
129 |
+ |
|
130 |
+ batches <- FRAGMENT(batches[[1]]) |
|
131 |
+ if (!is.null(as.altexp)) { |
|
132 |
+ originals <- FRAGMENT(originals[[1]]) |
|
130 | 133 |
} |
131 | 134 |
} |
135 |
+ } else if (length(batches)==0L) { |
|
136 |
+ stop("at least one SingleCellExperiment must be supplied") |
|
132 | 137 |
} else { |
133 | 138 |
preserve.single <- FALSE |
134 | 139 |
} |
135 | 140 |
|
136 |
- if (!is.null(as.altexp)) { |
|
137 |
- originals <- batches |
|
138 |
- batches <- lapply(batches, altExp, e=as.altexp) |
|
141 |
+ # Setting up the parallelization environment. |
|
142 |
+ if (.bpNotSharedOrUp(BPPARAM)) { |
|
143 |
+ bpstart(BPPARAM) |
|
144 |
+ on.exit(bpstop(BPPARAM), add=TRUE) |
|
139 | 145 |
} |
140 | 146 |
|
141 | 147 |
# Computing the averages and the size factors. |
... | ... |
@@ -7,13 +7,13 @@ |
7 | 7 |
multiBatchNorm( |
8 | 8 |
..., |
9 | 9 |
batch = NULL, |
10 |
- assay.type = "counts", |
|
11 | 10 |
norm.args = list(), |
12 |
- as.altexp = NULL, |
|
13 | 11 |
min.mean = 1, |
14 | 12 |
subset.row = NULL, |
15 | 13 |
normalize.all = FALSE, |
16 | 14 |
preserve.single = TRUE, |
15 |
+ assay.type = "counts", |
|
16 |
+ as.altexp = NULL, |
|
17 | 17 |
BPPARAM = SerialParam() |
18 | 18 |
) |
19 | 19 |
} |
... | ... |
@@ -30,13 +30,8 @@ this is flattened as if the objects inside were passed directly to \code{...}.} |
30 | 30 |
\item{batch}{A factor specifying the batch of origin for all cells when only a single object is supplied in \code{...}. |
31 | 31 |
This is ignored if multiple objects are present.} |
32 | 32 |
|
33 |
-\item{assay.type}{A string specifying which assay values contains the counts.} |
|
34 |
- |
|
35 | 33 |
\item{norm.args}{A named list of further arguments to pass to \code{\link[scuttle]{logNormCounts}}.} |
36 | 34 |
|
37 |
-\item{as.altexp}{String or integer scalar indicating the alternative Experiment to use in the function (see below for details). |
|
38 |
-All entries of \code{...} must contain the specified entry in their \code{\link{altExps}}.} |
|
39 |
- |
|
40 | 35 |
\item{min.mean}{A numeric scalar specifying the minimum (library size-adjusted) average count of genes to be used for normalization.} |
41 | 36 |
|
42 | 37 |
\item{subset.row}{A vector specifying which features to use for normalization.} |
... | ... |
@@ -45,6 +40,11 @@ All entries of \code{...} must contain the specified entry in their \code{\link{ |
45 | 40 |
|
46 | 41 |
\item{preserve.single}{A logical scalar indicating whether to combine the results into a single matrix if only one object was supplied in \code{...}.} |
47 | 42 |
|
43 |
+\item{assay.type}{A string specifying which assay values contains the counts.} |
|
44 |
+ |
|
45 |
+\item{as.altexp}{String or integer scalar indicating the alternative Experiment to use in the function (see below for details). |
|
46 |
+All entries of \code{...} must contain the specified entry in their \code{\link{altExps}}.} |
|
47 |
+ |
|
48 | 48 |
\item{BPPARAM}{A \linkS4class{BiocParallelParam} object specifying whether calculations should be parallelized.} |
49 | 49 |
} |
50 | 50 |
\value{ |