... | ... |
@@ -11,7 +11,7 @@ |
11 | 11 |
#' Rows represent features and columns represent cells. Alternatively, |
12 | 12 |
#' any matrix-like object that can be coerced to a sparse matrix of class |
13 | 13 |
#' "dgCMatrix" can be directly used as input. The matrix will automatically be |
14 |
-#' converted to a \linkS4class{SingleCellExperiment} object. |
|
14 |
+#' converted to a \linkS4class{SingleCellExperiment} object. |
|
15 | 15 |
#' @param useAssay A string specifying the name of the |
16 | 16 |
#' \link{assay} slot to use. Default "counts". |
17 | 17 |
#' @param altExpName The name for the \link{altExp} slot |
... | ... |
@@ -189,7 +189,7 @@ setMethod("celda_C", |
189 | 189 |
|
190 | 190 |
# Convert to sparse matrix |
191 | 191 |
x <- methods::as(x, "dgCMatrix") |
192 |
- |
|
192 |
+ |
|
193 | 193 |
ls <- list() |
194 | 194 |
ls[[useAssay]] <- x |
195 | 195 |
sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
... | ... |
@@ -11,7 +11,7 @@ |
11 | 11 |
#' Rows represent features and columns represent cells. Alternatively, |
12 | 12 |
#' any matrix-like object that can be coerced to a sparse matrix of class |
13 | 13 |
#' "dgCMatrix" can be directly used as input. The matrix will automatically be |
14 |
-#' converted to a \linkS4class{SingleCellExperiment} object. |
|
14 |
+#' converted to a \linkS4class{SingleCellExperiment} object. |
|
15 | 15 |
#' @param useAssay A string specifying the name of the |
16 | 16 |
#' \link{assay} slot to use. Default "counts". |
17 | 17 |
#' @param altExpName The name for the \link{altExp} slot |
... | ... |
@@ -223,7 +223,7 @@ setMethod("celda_CG", |
223 | 223 |
|
224 | 224 |
# Convert to sparse matrix |
225 | 225 |
x <- methods::as(x, "dgCMatrix") |
226 |
- |
|
226 |
+ |
|
227 | 227 |
ls <- list() |
228 | 228 |
ls[[useAssay]] <- x |
229 | 229 |
sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
... | ... |
@@ -11,7 +11,7 @@ |
11 | 11 |
#' Rows represent features and columns represent cells. Alternatively, |
12 | 12 |
#' any matrix-like object that can be coerced to a sparse matrix of class |
13 | 13 |
#' "dgCMatrix" can be directly used as input. The matrix will automatically be |
14 |
-#' converted to a \linkS4class{SingleCellExperiment} object. |
|
14 |
+#' converted to a \linkS4class{SingleCellExperiment} object. |
|
15 | 15 |
#' @param useAssay A string specifying the name of the |
16 | 16 |
#' \link{assay} slot to use. Default "counts". |
17 | 17 |
#' @param altExpName The name for the \link{altExp} slot |
... | ... |
@@ -173,7 +173,7 @@ setMethod("celda_G", |
173 | 173 |
|
174 | 174 |
# Convert to sparse matrix |
175 | 175 |
x <- methods::as(x, "dgCMatrix") |
176 |
- |
|
176 |
+ |
|
177 | 177 |
ls <- list() |
178 | 178 |
ls[[useAssay]] <- x |
179 | 179 |
sce <- SingleCellExperiment::SingleCellExperiment(assays = ls) |
... | ... |
@@ -553,7 +553,7 @@ featureModuleTable <- function(sce, |
553 | 553 |
altExpName = altExpName, |
554 | 554 |
type = "proportion") |
555 | 555 |
altExp <- SingleCellExperiment::altExp(sce, altExpName) |
556 |
- |
|
556 |
+ |
|
557 | 557 |
allGenes <- topRank(factorizeMatrix$proportions$module, n = nrow(altExp)) |
558 | 558 |
maxlen <- max(vapply(allGenes$names, length, integer(1))) |
559 | 559 |
|
... | ... |
@@ -44,14 +44,14 @@ setMethod("featureModuleLookup", signature(sce = "SingleCellExperiment"), |
44 | 44 |
by = "rownames") { |
45 | 45 |
|
46 | 46 |
modules <- as.numeric(celdaModules(sce, altExpName = altExpName)) |
47 |
- |
|
47 |
+ |
|
48 | 48 |
if (celdaModel(sce, altExpName = altExpName) %in% |
49 | 49 |
c("celda_CG", "celda_G")) { |
50 | 50 |
altExp <- SingleCellExperiment::altExp(sce, altExpName) |
51 | 51 |
featureIndex <- retrieveFeatureIndex(features, x = altExp, |
52 | 52 |
exactMatch = exactMatch, by = by) |
53 | 53 |
featureModules <- modules[featureIndex] |
54 |
- names(featureModules) <- features |
|
54 |
+ names(featureModules) <- features |
|
55 | 55 |
} else { |
56 | 56 |
stop("S4Vectors::metadata(altExp(sce, altExpName))$", |
57 | 57 |
"celda_parameters$model must be", |
... | ... |
@@ -60,5 +60,3 @@ setMethod("featureModuleLookup", signature(sce = "SingleCellExperiment"), |
60 | 60 |
return(featureModules) |
61 | 61 |
} |
62 | 62 |
) |
63 |
- |
|
64 |
- |
... | ... |
@@ -264,7 +264,7 @@ setMethod("moduleHeatmap", |
264 | 264 |
|
265 | 265 |
# Get max rowFontSize if multiple modules are selected |
266 | 266 |
if (is.null(rowFontSize)) { |
267 |
- if(length(featureIndices) > 1) { |
|
267 |
+ if (length(featureIndices) > 1) { |
|
268 | 268 |
maxlen <- max(unlist(lapply(featureIndices, length))) |
269 | 269 |
maxlen <- maxlen * sqrt(length(featureIndices)) |
270 | 270 |
rowFontSize <- min(200 / maxlen, 20) |
... | ... |
@@ -272,7 +272,7 @@ setMethod("moduleHeatmap", |
272 | 272 |
rowFontSize <- min(200 / length(featureIndices[[1]]), 20) |
273 | 273 |
} |
274 | 274 |
} |
275 |
- |
|
275 |
+ |
|
276 | 276 |
plts <- vector("list", length = length(featureModule)) |
277 | 277 |
for (i in seq(length(featureModule))) { |
278 | 278 |
plts[[i]] <- .plotModuleHeatmap(normCounts = normCounts, |
... | ... |
@@ -882,8 +882,8 @@ setMethod("plotRPC", |
882 | 882 |
diffMeansByK$L <- as.factor(diffMeansByK$L) |
883 | 883 |
diffMeansByK$rollmean <- data.table::frollmean( |
884 | 884 |
diffMeansByK$meanperpdiffK, n = n, align = "center") |
885 |
- diffMeansByK <- diffMeansByK[stats::complete.cases(diffMeansByK),] |
|
886 |
- |
|
885 |
+ diffMeansByK <- diffMeansByK[stats::complete.cases(diffMeansByK), ] |
|
886 |
+ |
|
887 | 887 |
if (nlevels(dt$L) > 1) { |
888 | 888 |
plot <- ggplot2::ggplot(dt[!is.na(perpdiffK), ], |
889 | 889 |
ggplot2::aes_string(x = "K", |
... | ... |
@@ -939,8 +939,8 @@ setMethod("plotRPC", |
939 | 939 |
diffMeansByL$L <- as.factor(diffMeansByL$L) |
940 | 940 |
diffMeansByL$rollmean <- data.table::frollmean( |
941 | 941 |
diffMeansByL$meanperpdiffL, n = n, align = "center") |
942 |
- diffMeansByL <- diffMeansByL[stats::complete.cases(diffMeansByL),] |
|
943 |
- |
|
942 |
+ diffMeansByL <- diffMeansByL[stats::complete.cases(diffMeansByL), ] |
|
943 |
+ |
|
944 | 944 |
plot <- ggplot2::ggplot(dt[!is.na(perpdiffL), ], |
945 | 945 |
ggplot2::aes_string(x = "L", y = "perpdiffL")) + |
946 | 946 |
ggplot2::geom_jitter(height = 0, width = 0.1, |
... | ... |
@@ -1002,8 +1002,8 @@ setMethod("plotRPC", |
1002 | 1002 |
diffMeansByK$K <- as.factor(diffMeansByK$K) |
1003 | 1003 |
diffMeansByK$rollmean <- data.table::frollmean( |
1004 | 1004 |
diffMeansByK$meanperpdiffK, n = n, align = "center") |
1005 |
- diffMeansByK <- diffMeansByK[stats::complete.cases(diffMeansByK),] |
|
1006 |
- |
|
1005 |
+ diffMeansByK <- diffMeansByK[stats::complete.cases(diffMeansByK), ] |
|
1006 |
+ |
|
1007 | 1007 |
plot <- ggplot2::ggplot(dt[!is.na(perpdiffK), ], |
1008 | 1008 |
ggplot2::aes_string(x = "K", |
1009 | 1009 |
y = "perpdiffK")) + |
... | ... |
@@ -1062,8 +1062,8 @@ setMethod("plotRPC", |
1062 | 1062 |
diffMeansByL$L <- as.factor(diffMeansByL$L) |
1063 | 1063 |
diffMeansByL$rollmean <- data.table::frollmean( |
1064 | 1064 |
diffMeansByL$meanperpdiffL, n = n, align = "center") |
1065 |
- diffMeansByL <- diffMeansByL[stats::complete.cases(diffMeansByL),] |
|
1066 |
- |
|
1065 |
+ diffMeansByL <- diffMeansByL[stats::complete.cases(diffMeansByL), ] |
|
1066 |
+ |
|
1067 | 1067 |
plot <- ggplot2::ggplot(dt[!is.na(perpdiffL), ], |
1068 | 1068 |
ggplot2::aes_string(x = "L", |
1069 | 1069 |
y = "perpdiffL")) + |
... | ... |
@@ -47,25 +47,26 @@ |
47 | 47 |
#' @return The plot as a ggplot object |
48 | 48 |
#' @export |
49 | 49 |
setGeneric("plotDimReduceGrid", |
50 |
- function(x, |
|
51 |
- reducedDimName, |
|
52 |
- dim1 = NULL, |
|
53 |
- dim2 = NULL, |
|
54 |
- useAssay = "counts", |
|
55 |
- altExpName = "featureSubset", |
|
56 |
- size = 1, |
|
57 |
- xlab = "Dimension_1", |
|
58 |
- ylab = "Dimension_2", |
|
59 |
- limits = c(-2, 2), |
|
60 |
- colorLow = "blue4", |
|
61 |
- colorMid = "grey90", |
|
62 |
- colorHigh = "firebrick1", |
|
63 |
- midpoint = 0, |
|
64 |
- varLabel = NULL, |
|
65 |
- ncol = NULL, |
|
66 |
- headers = NULL, |
|
67 |
- decreasing = FALSE) { |
|
68 |
- standardGeneric("plotDimReduceGrid")}) |
|
50 |
+ function(x, |
|
51 |
+ reducedDimName, |
|
52 |
+ dim1 = NULL, |
|
53 |
+ dim2 = NULL, |
|
54 |
+ useAssay = "counts", |
|
55 |
+ altExpName = "featureSubset", |
|
56 |
+ size = 1, |
|
57 |
+ xlab = "Dimension_1", |
|
58 |
+ ylab = "Dimension_2", |
|
59 |
+ limits = c(-2, 2), |
|
60 |
+ colorLow = "blue4", |
|
61 |
+ colorMid = "grey90", |
|
62 |
+ colorHigh = "firebrick1", |
|
63 |
+ midpoint = 0, |
|
64 |
+ varLabel = NULL, |
|
65 |
+ ncol = NULL, |
|
66 |
+ headers = NULL, |
|
67 |
+ decreasing = FALSE) { |
|
68 |
+ standardGeneric("plotDimReduceGrid") |
|
69 |
+ }) |
|
69 | 70 |
|
70 | 71 |
|
71 | 72 |
#' @rdname plotDimReduceGrid |
... | ... |
@@ -79,57 +80,57 @@ setGeneric("plotDimReduceGrid", |
79 | 80 |
#' varLabel = "tSNE") |
80 | 81 |
#' @export |
81 | 82 |
setMethod("plotDimReduceGrid", |
82 |
- signature(x = "SingleCellExperiment"), |
|
83 |
- function(x, |
|
84 |
- reducedDimName, |
|
85 |
- dim1 = NULL, |
|
86 |
- dim2 = NULL, |
|
87 |
- useAssay = "counts", |
|
88 |
- altExpName = "featureSubset", |
|
89 |
- size = 1, |
|
90 |
- xlab = "Dimension_1", |
|
91 |
- ylab = "Dimension_2", |
|
92 |
- limits = c(-2, 2), |
|
93 |
- colorLow = "blue4", |
|
94 |
- colorMid = "grey90", |
|
95 |
- colorHigh = "firebrick1", |
|
96 |
- midpoint = 0, |
|
97 |
- varLabel = NULL, |
|
98 |
- ncol = NULL, |
|
99 |
- headers = NULL, |
|
100 |
- decreasing = FALSE) { |
|
101 |
- |
|
102 |
- altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
103 |
- matrix <- SummarizedExperiment::assay(x, i = useAssay) |
|
104 |
- |
|
105 |
- if (is.null(dim1)) { |
|
106 |
- dim1 <- SingleCellExperiment::reducedDim(altExp, |
|
107 |
- reducedDimName)[, 1] |
|
108 |
- } |
|
109 |
- |
|
110 |
- if (is.null(dim2)) { |
|
111 |
- dim2 <- SingleCellExperiment::reducedDim(altExp, |
|
112 |
- reducedDimName)[, 2] |
|
113 |
- } |
|
114 |
- |
|
115 |
- g <- .plotDimReduceGrid(dim1 = dim1, |
|
116 |
- dim2 = dim2, |
|
117 |
- matrix = matrix, |
|
118 |
- size = size, |
|
119 |
- xlab = xlab, |
|
120 |
- ylab = ylab, |
|
121 |
- limits = limits, |
|
122 |
- colorLow = colorLow, |
|
123 |
- colorMid = colorMid, |
|
124 |
- colorHigh = colorHigh, |
|
125 |
- midpoint = midpoint, |
|
126 |
- varLabel = varLabel, |
|
127 |
- ncol = ncol, |
|
128 |
- headers = headers, |
|
129 |
- decreasing = decreasing) |
|
130 |
- return(g) |
|
131 |
- } |
|
132 |
-) |
|
83 |
+ signature(x = "SingleCellExperiment"), |
|
84 |
+ function(x, |
|
85 |
+ reducedDimName, |
|
86 |
+ dim1 = NULL, |
|
87 |
+ dim2 = NULL, |
|
88 |
+ useAssay = "counts", |
|
89 |
+ altExpName = "featureSubset", |
|
90 |
+ size = 1, |
|
91 |
+ xlab = "Dimension_1", |
|
92 |
+ ylab = "Dimension_2", |
|
93 |
+ limits = c(-2, 2), |
|
94 |
+ colorLow = "blue4", |
|
95 |
+ colorMid = "grey90", |
|
96 |
+ colorHigh = "firebrick1", |
|
97 |
+ midpoint = 0, |
|
98 |
+ varLabel = NULL, |
|
99 |
+ ncol = NULL, |
|
100 |
+ headers = NULL, |
|
101 |
+ decreasing = FALSE) { |
|
102 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
103 |
+ matrix <- SummarizedExperiment::assay(x, i = useAssay) |
|
104 |
+ |
|
105 |
+ if (is.null(dim1)) { |
|
106 |
+ dim1 <- SingleCellExperiment::reducedDim(altExp, |
|
107 |
+ reducedDimName)[, 1] |
|
108 |
+ } |
|
109 |
+ |
|
110 |
+ if (is.null(dim2)) { |
|
111 |
+ dim2 <- SingleCellExperiment::reducedDim(altExp, |
|
112 |
+ reducedDimName)[, 2] |
|
113 |
+ } |
|
114 |
+ |
|
115 |
+ g <- .plotDimReduceGrid( |
|
116 |
+ dim1 = dim1, |
|
117 |
+ dim2 = dim2, |
|
118 |
+ matrix = matrix, |
|
119 |
+ size = size, |
|
120 |
+ xlab = xlab, |
|
121 |
+ ylab = ylab, |
|
122 |
+ limits = limits, |
|
123 |
+ colorLow = colorLow, |
|
124 |
+ colorMid = colorMid, |
|
125 |
+ colorHigh = colorHigh, |
|
126 |
+ midpoint = midpoint, |
|
127 |
+ varLabel = varLabel, |
|
128 |
+ ncol = ncol, |
|
129 |
+ headers = headers, |
|
130 |
+ decreasing = decreasing |
|
131 |
+ ) |
|
132 |
+ return(g) |
|
133 |
+ }) |
|
133 | 134 |
|
134 | 135 |
|
135 | 136 |
#' @rdname plotDimReduceGrid |
... | ... |
@@ -145,151 +146,142 @@ setMethod("plotDimReduceGrid", |
145 | 146 |
#' varLabel = "tSNE") |
146 | 147 |
#' @export |
147 | 148 |
setMethod("plotDimReduceGrid", |
148 |
- signature(x = "ANY"), |
|
149 |
- function(x, |
|
150 |
- dim1, |
|
151 |
- dim2, |
|
152 |
- size = 1, |
|
153 |
- xlab = "Dimension_1", |
|
154 |
- ylab = "Dimension_2", |
|
155 |
- limits = c(-2, 2), |
|
156 |
- colorLow = "blue4", |
|
157 |
- colorMid = "grey90", |
|
158 |
- colorHigh = "firebrick1", |
|
159 |
- midpoint = 0, |
|
160 |
- varLabel = NULL, |
|
161 |
- ncol = NULL, |
|
162 |
- headers = NULL, |
|
163 |
- decreasing = FALSE) { |
|
164 |
- |
|
165 |
- x <- as.matrix(x) |
|
166 |
- g <- .plotDimReduceGrid(dim1 = dim1, |
|
167 |
- dim2 = dim2, |
|
168 |
- matrix = x, |
|
169 |
- size = size, |
|
170 |
- xlab = xlab, |
|
171 |
- ylab = ylab, |
|
172 |
- limits = limits, |
|
173 |
- colorLow = colorLow, |
|
174 |
- colorMid = colorMid, |
|
175 |
- colorHigh = colorHigh, |
|
176 |
- midpoint = midpoint, |
|
177 |
- varLabel = varLabel, |
|
178 |
- ncol = ncol, |
|
179 |
- headers = headers, |
|
180 |
- decreasing = decreasing) |
|
181 |
- return(g) |
|
182 |
- } |
|
183 |
-) |
|
149 |
+ signature(x = "ANY"), |
|
150 |
+ function(x, |
|
151 |
+ dim1, |
|
152 |
+ dim2, |
|
153 |
+ size = 1, |
|
154 |
+ xlab = "Dimension_1", |
|
155 |
+ ylab = "Dimension_2", |
|
156 |
+ limits = c(-2, 2), |
|
157 |
+ colorLow = "blue4", |
|
158 |
+ colorMid = "grey90", |
|
159 |
+ colorHigh = "firebrick1", |
|
160 |
+ midpoint = 0, |
|
161 |
+ varLabel = NULL, |
|
162 |
+ ncol = NULL, |
|
163 |
+ headers = NULL, |
|
164 |
+ decreasing = FALSE) { |
|
165 |
+ x <- as.matrix(x) |
|
166 |
+ g <- .plotDimReduceGrid( |
|
167 |
+ dim1 = dim1, |
|
168 |
+ dim2 = dim2, |
|
169 |
+ matrix = x, |
|
170 |
+ size = size, |
|
171 |
+ xlab = xlab, |
|
172 |
+ ylab = ylab, |
|
173 |
+ limits = limits, |
|
174 |
+ colorLow = colorLow, |
|
175 |
+ colorMid = colorMid, |
|
176 |
+ colorHigh = colorHigh, |
|
177 |
+ midpoint = midpoint, |
|
178 |
+ varLabel = varLabel, |
|
179 |
+ ncol = ncol, |
|
180 |
+ headers = headers, |
|
181 |
+ decreasing = decreasing |
|
182 |
+ ) |
|
183 |
+ return(g) |
|
184 |
+ }) |
|
184 | 185 |
|
185 | 186 |
|
186 | 187 |
#' @importFrom reshape2 melt |
187 | 188 |
.plotDimReduceGrid <- function(dim1, |
188 |
- dim2, |
|
189 |
- matrix, |
|
190 |
- size, |
|
191 |
- xlab, |
|
192 |
- ylab, |
|
193 |
- limits, |
|
194 |
- colorLow, |
|
195 |
- colorMid, |
|
196 |
- colorHigh, |
|
197 |
- midpoint, |
|
198 |
- varLabel, |
|
199 |
- ncol, |
|
200 |
- headers, |
|
201 |
- decreasing) { |
|
202 |
- |
|
203 |
- df <- data.frame(dim1, dim2, t(as.data.frame(matrix)), check.names = FALSE) |
|
204 |
- naIx <- is.na(dim1) | is.na(dim2) |
|
205 |
- df <- df[!naIx, ] |
|
206 |
- |
|
207 |
- m <- reshape2::melt(df, id.vars = c("dim1", "dim2")) |
|
208 |
- colnames(m) <- c(xlab, ylab, "facet", "Expression") |
|
209 |
- |
|
210 |
- if (!is.null(decreasing)) { |
|
211 |
- m <- m[order(m$facet, m$Expression, decreasing = decreasing), ] |
|
212 |
- } |
|
189 |
+ dim2, |
|
190 |
+ matrix, |
|
191 |
+ size, |
|
192 |
+ xlab, |
|
193 |
+ ylab, |
|
194 |
+ limits, |
|
195 |
+ colorLow, |
|
196 |
+ colorMid, |
|
197 |
+ colorHigh, |
|
198 |
+ midpoint, |
|
199 |
+ varLabel, |
|
200 |
+ ncol, |
|
201 |
+ headers, |
|
202 |
+ decreasing) { |
|
203 |
+ df <- |
|
204 |
+ data.frame(dim1, dim2, t(as.data.frame(matrix)), check.names = FALSE) |
|
205 |
+ naIx <- is.na(dim1) | is.na(dim2) |
|
206 |
+ df <- df[!naIx, ] |
|
213 | 207 |
|
214 |
- if (is.null(midpoint)) { |
|
215 |
- midpoint <- mean(m[, 4], trim = 0.1) |
|
216 |
- } |
|
208 |
+ m <- reshape2::melt(df, id.vars = c("dim1", "dim2")) |
|
209 |
+ colnames(m) <- c(xlab, ylab, "facet", "Expression") |
|
217 | 210 |
|
218 |
- varLabel <- gsub("_", " ", varLabel) |
|
219 |
- |
|
220 |
- if (isFALSE(is.null(headers))) { |
|
221 |
- names(headers) <- levels(m$facet) |
|
222 |
- headers <- ggplot2::as_labeller(headers) |
|
223 |
- |
|
224 |
- g <- ggplot2::ggplot( |
|
225 |
- m, |
|
226 |
- ggplot2::aes_string(x = xlab, y = ylab) |
|
227 |
- ) + |
|
228 |
- ggplot2::geom_point( |
|
229 |
- stat = "identity", |
|
230 |
- size = size, |
|
231 |
- ggplot2::aes_string(color = m$Expression) |
|
232 |
- ) + |
|
233 |
- ggplot2::theme_bw() + |
|
234 |
- ggplot2::scale_colour_gradient2( |
|
235 |
- limits = limits, |
|
236 |
- low = colorLow, |
|
237 |
- high = colorHigh, |
|
238 |
- mid = colorMid, |
|
239 |
- midpoint = midpoint, |
|
240 |
- name = varLabel |
|
241 |
- ) + |
|
242 |
- ggplot2::theme( |
|
243 |
- strip.background = ggplot2::element_blank(), |
|
244 |
- panel.grid.major = ggplot2::element_blank(), |
|
245 |
- panel.grid.minor = ggplot2::element_blank(), |
|
246 |
- panel.spacing = unit(0, "lines"), |
|
247 |
- panel.background = ggplot2::element_blank(), |
|
248 |
- axis.line = ggplot2::element_line(colour = "black") |
|
249 |
- ) |
|
250 |
- if (isFALSE(is.null(ncol))) { |
|
251 |
- g <- g + ggplot2::facet_wrap(~facet, |
|
252 |
- labeller = headers, |
|
253 |
- ncol = ncol |
|
254 |
- ) |
|
255 |
- } else { |
|
256 |
- g <- g + ggplot2::facet_wrap(~facet, labeller = headers) |
|
257 |
- } |
|
211 |
+ if (!is.null(decreasing)) { |
|
212 |
+ m <- m[order(m$facet, m$Expression, decreasing = decreasing), ] |
|
213 |
+ } |
|
214 |
+ |
|
215 |
+ if (is.null(midpoint)) { |
|
216 |
+ midpoint <- mean(m[, 4], trim = 0.1) |
|
217 |
+ } |
|
218 |
+ |
|
219 |
+ varLabel <- gsub("_", " ", varLabel) |
|
220 |
+ |
|
221 |
+ if (isFALSE(is.null(headers))) { |
|
222 |
+ names(headers) <- levels(m$facet) |
|
223 |
+ headers <- ggplot2::as_labeller(headers) |
|
224 |
+ |
|
225 |
+ g <- ggplot2::ggplot(m, |
|
226 |
+ ggplot2::aes_string(x = xlab, y = ylab)) + |
|
227 |
+ ggplot2::geom_point(stat = "identity", |
|
228 |
+ size = size, |
|
229 |
+ ggplot2::aes_string(color = m$Expression)) + |
|
230 |
+ ggplot2::theme_bw() + |
|
231 |
+ ggplot2::scale_colour_gradient2( |
|
232 |
+ limits = limits, |
|
233 |
+ low = colorLow, |
|
234 |
+ high = colorHigh, |
|
235 |
+ mid = colorMid, |
|
236 |
+ midpoint = midpoint, |
|
237 |
+ name = varLabel |
|
238 |
+ ) + |
|
239 |
+ ggplot2::theme( |
|
240 |
+ strip.background = ggplot2::element_blank(), |
|
241 |
+ panel.grid.major = ggplot2::element_blank(), |
|
242 |
+ panel.grid.minor = ggplot2::element_blank(), |
|
243 |
+ panel.spacing = unit(0, "lines"), |
|
244 |
+ panel.background = ggplot2::element_blank(), |
|
245 |
+ axis.line = ggplot2::element_line(colour = "black") |
|
246 |
+ ) |
|
247 |
+ if (isFALSE(is.null(ncol))) { |
|
248 |
+ g <- g + ggplot2::facet_wrap(~ facet, |
|
249 |
+ labeller = headers, |
|
250 |
+ ncol = ncol) |
|
258 | 251 |
} else { |
259 |
- g <- ggplot2::ggplot( |
|
260 |
- m, |
|
261 |
- ggplot2::aes_string(x = xlab, y = ylab) |
|
262 |
- ) + |
|
263 |
- ggplot2::geom_point( |
|
264 |
- stat = "identity", |
|
265 |
- size = size, |
|
266 |
- ggplot2::aes_string(color = m$Expression) |
|
267 |
- ) + |
|
268 |
- ggplot2::facet_wrap(~facet) + |
|
269 |
- ggplot2::theme_bw() + |
|
270 |
- ggplot2::scale_colour_gradient2( |
|
271 |
- limits = limits, |
|
272 |
- low = colorLow, |
|
273 |
- high = colorHigh, |
|
274 |
- mid = colorMid, |
|
275 |
- midpoint = midpoint, |
|
276 |
- name = varLabel |
|
277 |
- ) + |
|
278 |
- ggplot2::theme( |
|
279 |
- strip.background = ggplot2::element_blank(), |
|
280 |
- panel.grid.major = ggplot2::element_blank(), |
|
281 |
- panel.grid.minor = ggplot2::element_blank(), |
|
282 |
- panel.spacing = unit(0, "lines"), |
|
283 |
- panel.background = ggplot2::element_blank(), |
|
284 |
- axis.line = ggplot2::element_line(colour = "black") |
|
285 |
- ) |
|
286 |
- if (isFALSE(is.null(ncol))) { |
|
287 |
- g <- g + ggplot2::facet_wrap(~facet, ncol = ncol) |
|
288 |
- } else { |
|
289 |
- g <- g + ggplot2::facet_wrap(~facet) |
|
290 |
- } |
|
252 |
+ g <- g + ggplot2::facet_wrap(~ facet, labeller = headers) |
|
291 | 253 |
} |
292 |
- return(g) |
|
254 |
+ } else { |
|
255 |
+ g <- ggplot2::ggplot(m, |
|
256 |
+ ggplot2::aes_string(x = xlab, y = ylab)) + |
|
257 |
+ ggplot2::geom_point(stat = "identity", |
|
258 |
+ size = size, |
|
259 |
+ ggplot2::aes_string(color = m$Expression)) + |
|
260 |
+ ggplot2::facet_wrap(~ facet) + |
|
261 |
+ ggplot2::theme_bw() + |
|
262 |
+ ggplot2::scale_colour_gradient2( |
|
263 |
+ limits = limits, |
|
264 |
+ low = colorLow, |
|
265 |
+ high = colorHigh, |
|
266 |
+ mid = colorMid, |
|
267 |
+ midpoint = midpoint, |
|
268 |
+ name = varLabel |
|
269 |
+ ) + |
|
270 |
+ ggplot2::theme( |
|
271 |
+ strip.background = ggplot2::element_blank(), |
|
272 |
+ panel.grid.major = ggplot2::element_blank(), |
|
273 |
+ panel.grid.minor = ggplot2::element_blank(), |
|
274 |
+ panel.spacing = unit(0, "lines"), |
|
275 |
+ panel.background = ggplot2::element_blank(), |
|
276 |
+ axis.line = ggplot2::element_line(colour = "black") |
|
277 |
+ ) |
|
278 |
+ if (isFALSE(is.null(ncol))) { |
|
279 |
+ g <- g + ggplot2::facet_wrap(~ facet, ncol = ncol) |
|
280 |
+ } else { |
|
281 |
+ g <- g + ggplot2::facet_wrap(~ facet) |
|
282 |
+ } |
|
283 |
+ } |
|
284 |
+ return(g) |
|
293 | 285 |
} |
294 | 286 |
|
295 | 287 |
|
... | ... |
@@ -366,30 +358,30 @@ setMethod("plotDimReduceGrid", |
366 | 358 |
#' @return The plot as a ggplot object |
367 | 359 |
#' @export |
368 | 360 |
setGeneric("plotDimReduceFeature", function(x, |
369 |
- features, |
|
370 |
- reducedDimName = NULL, |
|
371 |
- displayName = NULL, |
|
372 |
- dim1 = NULL, |
|
373 |
- dim2 = NULL, |
|
374 |
- headers = NULL, |
|
375 |
- useAssay = "counts", |
|
376 |
- altExpName = "featureSubset", |
|
377 |
- normalize = FALSE, |
|
378 |
- zscore = TRUE, |
|
379 |
- exactMatch = TRUE, |
|
380 |
- trim = c(-2, 2), |
|
381 |
- limits = c(-2, 2), |
|
382 |
- size = 0.5, |
|
383 |
- xlab = NULL, |
|
384 |
- ylab = NULL, |
|
385 |
- colorLow = "blue4", |
|
386 |
- colorMid = "grey90", |
|
387 |
- colorHigh = "firebrick1", |
|
388 |
- midpoint = 0, |
|
389 |
- ncol = NULL, |
|
390 |
- decreasing = FALSE) { |
|
391 |
- |
|
392 |
- standardGeneric("plotDimReduceFeature")}) |
|
361 |
+ features, |
|
362 |
+ reducedDimName = NULL, |
|
363 |
+ displayName = NULL, |
|
364 |
+ dim1 = NULL, |
|
365 |
+ dim2 = NULL, |
|
366 |
+ headers = NULL, |
|
367 |
+ useAssay = "counts", |
|
368 |
+ altExpName = "featureSubset", |
|
369 |
+ normalize = FALSE, |
|
370 |
+ zscore = TRUE, |
|
371 |
+ exactMatch = TRUE, |
|
372 |
+ trim = c(-2, 2), |
|
373 |
+ limits = c(-2, 2), |
|
374 |
+ size = 0.5, |
|
375 |
+ xlab = NULL, |
|
376 |
+ ylab = NULL, |
|
377 |
+ colorLow = "blue4", |
|
378 |
+ colorMid = "grey90", |
|
379 |
+ colorHigh = "firebrick1", |
|
380 |
+ midpoint = 0, |
|
381 |
+ ncol = NULL, |
|
382 |
+ decreasing = FALSE) { |
|
383 |
+ standardGeneric("plotDimReduceFeature") |
|
384 |
+}) |
|
393 | 385 |
|
394 | 386 |
|
395 | 387 |
#' @rdname plotDimReduceFeature |
... | ... |
@@ -403,92 +395,91 @@ setGeneric("plotDimReduceFeature", function(x, |
403 | 395 |
#' exactMatch = TRUE) |
404 | 396 |
#' @export |
405 | 397 |
setMethod("plotDimReduceFeature", |
406 |
- signature(x = "SingleCellExperiment"), |
|
407 |
- function(x, |
|
408 |
- features, |
|
409 |
- reducedDimName, |
|
410 |
- displayName = NULL, |
|
411 |
- dim1 = 1, |
|
412 |
- dim2 = 2, |
|
413 |
- headers = NULL, |
|
414 |
- useAssay = "counts", |
|
415 |
- altExpName = "featureSubset", |
|
416 |
- normalize = FALSE, |
|
417 |
- zscore = TRUE, |
|
418 |
- exactMatch = TRUE, |
|
419 |
- trim = c(-2, 2), |
|
420 |
- limits = c(-2, 2), |
|
421 |
- size = 0.5, |
|
422 |
- xlab = NULL, |
|
423 |
- ylab = NULL, |
|
424 |
- colorLow = "blue4", |
|
425 |
- colorMid = "grey90", |
|
426 |
- colorHigh = "firebrick1", |
|
427 |
- midpoint = 0, |
|
428 |
- ncol = NULL, |
|
429 |
- decreasing = FALSE) { |
|
430 |
- |
|
431 |
- altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
432 |
- counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
433 |
- reddim <- .processReducedDim(x = altExp, |
|
434 |
- reducedDimName = reducedDimName, |
|
435 |
- dim1 = dim1, |
|
436 |
- dim2 = dim2, |
|
437 |
- xlab = xlab, |
|
438 |
- ylab = ylab) |
|
439 |
- |
|
440 |
- if (isFALSE(is.null(displayName))) { |
|
441 |
- featuresIx <- retrieveFeatureIndex(features, |
|
442 |
- x, |
|
443 |
- by = displayName, |
|
444 |
- exactMatch = exactMatch) |
|
445 |
- headers <- SummarizedExperiment::rowData(x)[[ |
|
446 |
- displayName]][featuresIx] |
|
447 |
- } else { |
|
448 |
- featuresIx <- retrieveFeatureIndex(features, |
|
449 |
- counts, |
|
450 |
- by = "rownames", |
|
451 |
- exactMatch = exactMatch) |
|
398 |
+ signature(x = "SingleCellExperiment"), |
|
399 |
+ function(x, |
|
400 |
+ features, |
|
401 |
+ reducedDimName, |
|
402 |
+ displayName = NULL, |
|
403 |
+ dim1 = 1, |
|
404 |
+ dim2 = 2, |
|
405 |
+ headers = NULL, |
|
406 |
+ useAssay = "counts", |
|
407 |
+ altExpName = "featureSubset", |
|
408 |
+ normalize = FALSE, |
|
409 |
+ zscore = TRUE, |
|
410 |
+ exactMatch = TRUE, |
|
411 |
+ trim = c(-2, 2), |
|
412 |
+ limits = c(-2, 2), |
|
413 |
+ size = 0.5, |
|
414 |
+ xlab = NULL, |
|
415 |
+ ylab = NULL, |
|
416 |
+ colorLow = "blue4", |
|
417 |
+ colorMid = "grey90", |
|
418 |
+ colorHigh = "firebrick1", |
|
419 |
+ midpoint = 0, |
|
420 |
+ ncol = NULL, |
|
421 |
+ decreasing = FALSE) { |
|
422 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
423 |
+ counts <- SummarizedExperiment::assay(x, i = useAssay) |
|
424 |
+ reddim <- .processReducedDim( |
|
425 |
+ x = altExp, |
|
426 |
+ reducedDimName = reducedDimName, |
|
427 |
+ dim1 = dim1, |
|
428 |
+ dim2 = dim2, |
|
429 |
+ xlab = xlab, |
|
430 |
+ ylab = ylab |
|
431 |
+ ) |
|
452 | 432 |
|
453 |
- if (isFALSE(is.null(headers))) { |
|
433 |
+ if (isFALSE(is.null(displayName))) { |
|
434 |
+ featuresIx <- retrieveFeatureIndex(features, |
|
435 |
+ x, |
|
436 |
+ by = displayName, |
|
437 |
+ exactMatch = exactMatch) |
|
438 |
+ headers <- SummarizedExperiment::rowData(x)[[displayName]][featuresIx] |
|
439 |
+ } else { |
|
440 |
+ featuresIx <- retrieveFeatureIndex(features, |
|
441 |
+ counts, |
|
442 |
+ by = "rownames", |
|
443 |
+ exactMatch = exactMatch) |
|
444 |
+ |
|
445 |
+ if (isFALSE(is.null(headers))) { |
|
454 | 446 |
if (length(headers) != length(features)) { |
455 |
- stop( |
|
456 |
- "Headers ", |
|
457 |
- headers, |
|
458 |
- " should be the same length as features ", |
|
459 |
- features |
|
460 |
- ) |
|
447 |
+ stop("Headers ", |
|
448 |
+ headers, |
|
449 |
+ " should be the same length as features ", |
|
450 |
+ features) |
|
461 | 451 |
} |
462 | 452 |
|
463 | 453 |
if (isFALSE(exactMatch)) { |
464 |
- warning("exactMatch is FALSE. headers will not be used!") |
|
465 |
- headers <- NULL |
|
454 |
+ warning("exactMatch is FALSE. headers will not be used!") |
|
455 |
+ headers <- NULL |
|
466 | 456 |
} |
457 |
+ } |
|
467 | 458 |
} |
468 |
- } |
|
469 |
- |
|
470 |
- g <- .plotDimReduceFeature(dim1 = reddim$dim1, |
|
471 |
- dim2 = reddim$dim2, |
|
472 |
- counts = counts, |
|
473 |
- features = features, |
|
474 |
- headers = headers, |
|
475 |
- normalize = normalize, |
|
476 |
- zscore = zscore, |
|
477 |
- featuresIx = featuresIx, |
|
478 |
- trim = trim, |
|
479 |
- limits = limits, |
|
480 |
- size = size, |
|
481 |
- xlab = reddim$xlab, |
|
482 |
- ylab = reddim$ylab, |
|
483 |
- colorLow = colorLow, |
|
484 |
- colorMid = colorMid, |
|
485 |
- colorHigh = colorHigh, |
|
486 |
- midpoint = midpoint, |
|
487 |
- ncol = ncol, |
|
488 |
- decreasing = decreasing) |
|
489 |
- return(g) |
|
490 |
- } |
|
491 |
-) |
|
459 |
+ |
|
460 |
+ g <- .plotDimReduceFeature( |
|
461 |
+ dim1 = reddim$dim1, |
|
462 |
+ dim2 = reddim$dim2, |
|
463 |
+ counts = counts, |
|
464 |
+ features = features, |
|
465 |
+ headers = headers, |
|
466 |
+ normalize = normalize, |
|
467 |
+ zscore = zscore, |
|
468 |
+ featuresIx = featuresIx, |
|
469 |
+ trim = trim, |
|
470 |
+ limits = limits, |
|
471 |
+ size = size, |
|
472 |
+ xlab = reddim$xlab, |
|
473 |
+ ylab = reddim$ylab, |
|
474 |
+ colorLow = colorLow, |
|
475 |
+ colorMid = colorMid, |
|
476 |
+ colorHigh = colorHigh, |
|
477 |
+ midpoint = midpoint, |
|
478 |
+ ncol = ncol, |
|
479 |
+ decreasing = decreasing |
|
480 |
+ ) |
|
481 |
+ return(g) |
|
482 |
+ }) |
|
492 | 483 |
|
493 | 484 |
|
494 | 485 |
#' @rdname plotDimReduceFeature |
... | ... |
@@ -504,93 +495,90 @@ setMethod("plotDimReduceFeature", |
504 | 495 |
#' exactMatch = TRUE) |
505 | 496 |
#' @export |
506 | 497 |
setMethod("plotDimReduceFeature", |
507 |
- signature(x = "ANY"), |
|
508 |
- function(x, |
|
509 |
- features, |
|
510 |
- dim1, |
|
511 |
- dim2, |
|
512 |
- headers = NULL, |
|
513 |
- normalize = FALSE, |
|
514 |
- zscore = TRUE, |
|
515 |
- exactMatch = TRUE, |
|
516 |
- trim = c(-2, 2), |
|
517 |
- limits = c(-2, 2), |
|
518 |
- size = 0.5, |
|
519 |
- xlab = "Dimension_1", |
|
520 |
- ylab = "Dimension_2", |
|
521 |
- colorLow = "blue4", |
|
522 |
- colorMid = "grey90", |
|
523 |
- colorHigh = "firebrick1", |
|
524 |
- midpoint = 0, |
|
525 |
- ncol = NULL, |
|
526 |
- decreasing = FALSE) { |
|
527 |
- |
|
528 |
- x <- as.matrix(x) |
|
529 |
- if (isFALSE(is.null(headers))) { |
|
530 |
- if (length(headers) != length(features)) { |
|
531 |
- stop( |
|
532 |
- "Headers ", |
|
533 |
- headers, |
|
534 |
- " should be the same length as features ", |
|
535 |
- features |
|
536 |
- ) |
|
537 |
- } |
|
538 |
- |
|
539 |
- if (isFALSE(exactMatch)) { |
|
498 |
+ signature(x = "ANY"), |
|
499 |
+ function(x, |
|
500 |
+ features, |
|
501 |
+ dim1, |
|
502 |
+ dim2, |
|
503 |
+ headers = NULL, |
|
504 |
+ normalize = FALSE, |
|
505 |
+ zscore = TRUE, |
|
506 |
+ exactMatch = TRUE, |
|
507 |
+ trim = c(-2, 2), |
|
508 |
+ limits = c(-2, 2), |
|
509 |
+ size = 0.5, |
|
510 |
+ xlab = "Dimension_1", |
|
511 |
+ ylab = "Dimension_2", |
|
512 |
+ colorLow = "blue4", |
|
513 |
+ colorMid = "grey90", |
|
514 |
+ colorHigh = "firebrick1", |
|
515 |
+ midpoint = 0, |
|
516 |
+ ncol = NULL, |
|
517 |
+ decreasing = FALSE) { |
|
518 |
+ x <- as.matrix(x) |
|
519 |
+ if (isFALSE(is.null(headers))) { |
|
520 |
+ if (length(headers) != length(features)) { |
|
521 |
+ stop("Headers ", |
|
522 |
+ headers, |
|
523 |
+ " should be the same length as features ", |
|
524 |
+ features) |
|
525 |
+ } |
|
526 |
+ |
|
527 |
+ if (isFALSE(exactMatch)) { |
|
540 | 528 |
warning("exactMatch is FALSE. headers will not be used!") |
541 | 529 |
headers <- NULL |
530 |
+ } |
|
542 | 531 |
} |
543 |
- } |
|
544 |
- |
|
545 |
- featuresIx <- retrieveFeatureIndex(features, |
|
546 |
- x, |
|
547 |
- by = "rownames", |
|
548 |
- exactMatch = exactMatch) |
|
549 |
- |
|
550 |
- g <- .plotDimReduceFeature(dim1 = dim1, |
|
551 |
- dim2 = dim2, |
|
552 |
- counts = x, |
|
553 |
- features = features, |
|
554 |
- headers = headers, |
|
555 |
- normalize = normalize, |
|
556 |
- zscore = zscore, |
|
557 |
- featuresIx = featuresIx, |
|
558 |
- trim = trim, |
|
559 |
- limits = limits, |
|
560 |
- size = size, |
|
561 |
- xlab = xlab, |
|
562 |
- ylab = ylab, |
|
563 |
- colorLow = colorLow, |
|
564 |
- colorMid = colorMid, |
|
565 |
- colorHigh = colorHigh, |
|
566 |
- midpoint = midpoint, |
|
567 |
- ncol = ncol, |
|
568 |
- decreasing = decreasing) |
|
569 |
- return(g) |
|
570 |
- } |
|
571 |
-) |
|
572 | 532 |
|
533 |
+ featuresIx <- retrieveFeatureIndex(features, |
|
534 |
+ x, |
|
535 |
+ by = "rownames", |
|
536 |
+ exactMatch = exactMatch) |
|
537 |
+ |
|
538 |
+ g <- .plotDimReduceFeature( |
|
539 |
+ dim1 = dim1, |
|
540 |
+ dim2 = dim2, |
|
541 |
+ counts = x, |
|
542 |
+ features = features, |
|
543 |
+ headers = headers, |
|
544 |
+ normalize = normalize, |
|
545 |
+ zscore = zscore, |
|
546 |
+ featuresIx = featuresIx, |
|
547 |
+ trim = trim, |
|
548 |
+ limits = limits, |
|
549 |
+ size = size, |
|
550 |
+ xlab = xlab, |
|
551 |
+ ylab = ylab, |
|
552 |
+ colorLow = colorLow, |
|
553 |
+ colorMid = colorMid, |
|
554 |
+ colorHigh = colorHigh, |
|
555 |
+ midpoint = midpoint, |
|
556 |
+ ncol = ncol, |
|
557 |
+ decreasing = decreasing |
|
558 |
+ ) |
|
559 |
+ return(g) |
|
560 |
+ }) |
|
573 | 561 |
|
574 |
-.plotDimReduceFeature <- function(dim1, |
|
575 |
- dim2, |
|
576 |
- counts, |
|
577 |
- features, |
|
578 |
- headers, |
|
579 |
- normalize, |
|
580 |
- zscore, |
|
581 |
- featuresIx, |
|
582 |
- trim, |
|
583 |
- limits, |
|
584 |
- size, |
|
585 |
- xlab, |
|
586 |
- ylab, |
|
587 |
- colorLow, |
|
588 |
- colorMid, |
|
589 |
- colorHigh, |
|
590 |
- midpoint, |
|
591 |
- ncol, |
|
592 |
- decreasing) { |
|
593 | 562 |
|
563 |
+.plotDimReduceFeature <- function(dim1, |
|
564 |
+ dim2, |
|
565 |
+ counts, |
|
566 |
+ features, |
|
567 |
+ headers, |
|
568 |
+ normalize, |
|
569 |
+ zscore, |
|
570 |
+ featuresIx, |
|
571 |
+ trim, |
|
572 |
+ limits, |
|
573 |
+ size, |
|
574 |
+ xlab, |
|
575 |
+ ylab, |
|
576 |
+ colorLow, |
|
577 |
+ colorMid, |
|
578 |
+ colorHigh, |
|
579 |
+ midpoint, |
|
580 |
+ ncol, |
|
581 |
+ decreasing) { |
|
594 | 582 |
# Perform checks |
595 | 583 |
if (is.null(features)) { |
596 | 584 |
stop("at least one feature is required to create a plot") |
... | ... |
@@ -614,10 +602,8 @@ setMethod("plotDimReduceFeature", |
614 | 602 |
|
615 | 603 |
if (!is.null(trim)) { |
616 | 604 |
if (length(trim) != 2) { |
617 |
- stop( |
|
618 |
- "'trim' should be a 2 element vector", |
|
619 |
- "specifying the lower and upper boundaries" |
|
620 |
- ) |
|
605 |
+ stop("'trim' should be a 2 element vector", |
|
606 |
+ "specifying the lower and upper boundaries") |
|
621 | 607 |
} |
622 | 608 |
trim <- sort(trim) |
623 | 609 |
counts[counts < trim[1]] <- trim[1] |
... | ... |
@@ -695,24 +681,25 @@ setMethod("plotDimReduceFeature", |
695 | 681 |
#' @return The plot as a ggplot object |
696 | 682 |
#' @export |
697 | 683 |
setGeneric("plotDimReduceModule", |
698 |
- function(x, |
|
699 |
- reducedDimName, |
|
700 |
- useAssay = "counts", |
|
701 |
- altExpName = "featureSubset", |
|
702 |
- celdaMod, |
|
703 |
- modules = NULL, |
|
704 |
- dim1 = NULL, |
|
705 |
- dim2 = NULL, |
|
706 |
- size = 0.5, |
|
707 |
- xlab = NULL, |
|
708 |
- ylab = NULL, |
|
709 |
- rescale = TRUE, |
|
710 |
- limits = c(0, 1), |
|
711 |
- colorLow = "grey90", |
|
712 |
- colorHigh = "firebrick1", |
|
713 |
- ncol = NULL, |
|
714 |
- decreasing = FALSE) { |
|
715 |
- standardGeneric("plotDimReduceModule")}) |
|
684 |
+ function(x, |
|
685 |
+ reducedDimName, |
|
686 |
+ useAssay = "counts", |
|
687 |
+ altExpName = "featureSubset", |
|
688 |
+ celdaMod, |
|
689 |
+ modules = NULL, |
|
690 |
+ dim1 = NULL, |
|
691 |
+ dim2 = NULL, |
|
692 |
+ size = 0.5, |
|
693 |
+ xlab = NULL, |
|
694 |
+ ylab = NULL, |
|
695 |
+ rescale = TRUE, |
|
696 |
+ limits = c(0, 1), |
|
697 |
+ colorLow = "grey90", |
|
698 |
+ colorHigh = "firebrick1", |
|
699 |
+ ncol = NULL, |
|
700 |
+ decreasing = FALSE) { |
|
701 |
+ standardGeneric("plotDimReduceModule") |
|
702 |
+ }) |
|
716 | 703 |
|
717 | 704 |
|
718 | 705 |
#' @rdname plotDimReduceModule |
... | ... |
@@ -724,54 +711,56 @@ setGeneric("plotDimReduceModule", |
724 | 711 |
#' modules = c("1", "2")) |
725 | 712 |
#' @export |
726 | 713 |
setMethod("plotDimReduceModule", |
727 |
- signature(x = "SingleCellExperiment"), |
|
728 |
- function(x, |
|
729 |
- reducedDimName, |
|
730 |
- useAssay = "counts", |
|
731 |
- altExpName = "featureSubset", |
|
732 |
- modules = NULL, |
|
733 |
- dim1 = 1, |
|
734 |
- dim2 = 2, |
|
735 |
- size = 0.5, |
|
736 |
- xlab = NULL, |
|
737 |
- ylab = NULL, |
|
738 |
- rescale = TRUE, |
|
739 |
- limits = c(0, 1), |
|
740 |
- colorLow = "grey90", |
|
741 |
- colorHigh = "firebrick1", |
|
742 |
- ncol = NULL, |
|
743 |
- decreasing = FALSE) { |
|
744 |
- |
|
745 |
- # Get reduced dim object |
|
746 |
- altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
747 |
- reddim <- .processReducedDim(x = altExp, |
|
748 |
- reducedDimName = reducedDimName, |
|
749 |
- dim1 = dim1, |
|
750 |
- dim2 = dim2, |
|
751 |
- xlab = xlab, |
|
752 |
- ylab = ylab) |
|
753 |
- |
|
754 |
- factorized <- factorizeMatrix(x, |
|
755 |
- useAssay = useAssay, |
|
756 |
- altExpName = altExpName, |
|
757 |
- type = "proportion") |
|
758 |
- |
|
759 |
- g <- .plotDimReduceModule(dim1 = reddim$dim1, |
|
760 |
- dim2 = reddim$dim2, |
|
761 |
- factorized = factorized, |
|
762 |
- modules = modules, |
|
763 |
- rescale = rescale, |
|
764 |
- limits = limits, |
|
765 |
- size = size, |
|
766 |
- xlab = reddim$xlab, |
|
767 |
- ylab = reddim$ylab, |
|
768 |
- colorLow = colorLow, |
|
769 |
- colorHigh = colorHigh, |
|
770 |
- ncol = ncol, |
|
771 |
- decreasing = decreasing) |
|
772 |
- return(g) |
|
773 |
- } |
|
774 |
-) |
|
714 |
+ signature(x = "SingleCellExperiment"), |
|
715 |
+ function(x, |
|
716 |
+ reducedDimName, |
|
717 |
+ useAssay = "counts", |
|
718 |
+ altExpName = "featureSubset", |
|
719 |
+ modules = NULL, |
|
720 |
+ dim1 = 1, |
|
721 |
+ dim2 = 2, |
|
722 |
+ size = 0.5, |
|
723 |
+ xlab = NULL, |
|
724 |
+ ylab = NULL, |
|
725 |
+ rescale = TRUE, |
|
726 |
+ limits = c(0, 1), |
|
727 |
+ colorLow = "grey90", |
|
728 |
+ colorHigh = "firebrick1", |
|
729 |
+ ncol = NULL, |
|
730 |
+ decreasing = FALSE) { |
|
731 |
+ # Get reduced dim object |
|
732 |
+ altExp <- SingleCellExperiment::altExp(x, altExpName) |
|
733 |
+ reddim <- .processReducedDim( |
|
734 |
+ x = altExp, |
|
735 |
+ reducedDimName = reducedDimName, |
|
736 |
+ dim1 = dim1, |
|
737 |
+ dim2 = dim2, |
|
738 |
+ xlab = xlab, |
|
739 |
+ ylab = ylab |
|
740 |
+ ) |
|
741 |
+ |
|
742 |
+ factorized <- factorizeMatrix(x, |
|
743 |
+ useAssay = useAssay, |
|
744 |
+ altExpName = altExpName, |
|
745 |
+ type = "proportion") |
|
746 |
+ |
|
747 |
+ g <- .plotDimReduceModule( |
|
748 |
+ dim1 = reddim$dim1, |
|
749 |
+ dim2 = reddim$dim2, |
|
750 |
+ factorized = factorized, |
|
751 |
+ modules = modules, |
|
752 |
+ rescale = rescale, |
|
753 |
+ limits = limits, |
|
754 |
+ size = size, |
|
755 |
+ xlab = reddim$xlab, |
|
756 |
+ ylab = reddim$ylab, |
|
757 |
+ colorLow = colorLow, |
|
758 |
+ colorHigh = colorHigh, |
|
759 |
+ ncol = ncol, |
|
760 |
+ decreasing = decreasing |
|
761 |
+ ) |
|
762 |
+ return(g) |
|
763 |
+ }) |
|
775 | 764 |
|
776 | 765 |
|
777 | 766 |
#' @rdname plotDimReduceModule |
... | ... |
@@ -786,118 +775,127 @@ setMethod("plotDimReduceModule", |
786 | 775 |
#' modules = c("1", "2")) |
787 | 776 |
#' @export |
788 | 777 |
setMethod("plotDimReduceModule", |
789 |
- signature(x = "ANY"), |
|
790 |
- function(x, |
|
791 |
- celdaMod, |
|
792 |
- modules = NULL, |
|
793 |
- dim1, |
|
794 |
- dim2, |
|
795 |
- size = 0.5, |
|
796 |
- xlab = "Dimension_1", |
|
797 |
- ylab = "Dimension_2", |
|
798 |
- rescale = TRUE, |
|
799 |
- limits = c(0, 1), |
|
800 |
- colorLow = "grey90", |
|
801 |
- colorHigh = "firebrick1", |
|
802 |
- ncol = NULL, |
|
803 |
- decreasing = FALSE) { |
|
804 |
- |
|
805 |
- factorized <- factorizeMatrix(x = x, celdaMod = celdaMod) |
|
806 |
- reddim <- .processReducedDim(x = x, |
|
807 |
- dim1 = dim1, |
|
808 |
- dim2 = dim2, |
|
809 |
- xlab = xlab, |
|
810 |
- ylab = ylab) |
|
811 |
- |
|
812 |
- g <- .plotDimReduceModule(dim1 = reddim$dim1, |
|
813 |
- dim2 = reddim$dim2, |
|
814 |
- factorized = factorized, |
|
815 |
- modules = modules, |
|
816 |
- rescale = rescale, |
|
817 |
- limits = limits, |
|
818 |
- size = size, |
|
819 |
- xlab = reddim$xlab, |
|
820 |
- ylab = reddim$ylab, |
|
821 |
- colorLow = colorLow, |
|
822 |
- colorHigh = colorHigh, |
|
823 |
- ncol = ncol, |
|
824 |
- decreasing = decreasing) |
|
825 |
- return(g) |
|
826 |
- } |
|
827 |
-) |
|
778 |
+ signature(x = "ANY"), |
|
779 |
+ function(x, |
|
780 |
+ celdaMod, |
|
781 |
+ modules = NULL, |
|
782 |
+ dim1, |
|
783 |
+ dim2, |
|
784 |
+ size = 0.5, |
|
785 |
+ xlab = "Dimension_1", |
|
786 |
+ ylab = "Dimension_2", |
|
787 |
+ rescale = TRUE, |
|
788 |
+ limits = c(0, 1), |
|
789 |
+ colorLow = "grey90", |
|
790 |
+ colorHigh = "firebrick1", |
|
791 |
+ ncol = NULL, |
|
792 |
+ decreasing = FALSE) { |
|
793 |
+ factorized <- factorizeMatrix(x = x, celdaMod = celdaMod) |
|
794 |
+ reddim <- .processReducedDim( |
|
795 |
+ x = x, |
|
796 |
+ dim1 = dim1, |
|
797 |
+ dim2 = dim2, |
|
798 |
+ xlab = xlab, |
|
799 |
+ ylab = ylab |
|
800 |
+ ) |
|
801 |
+ |
|
802 |
+ g <- .plotDimReduceModule( |
|
803 |
+ dim1 = reddim$dim1, |
|
804 |
+ dim2 = reddim$dim2, |
|
805 |
+ factorized = factorized, |
|
806 |
+ modules = modules, |
|
807 |
+ rescale = rescale, |
|
808 |
+ limits = limits, |
|
809 |
+ size = size, |
|
810 |
+ xlab = reddim$xlab, |
|
811 |
+ ylab = reddim$ylab, |
|
812 |
+ colorLow = colorLow, |
|
813 |
+ colorHigh = colorHigh, |
|
814 |
+ ncol = ncol, |
|
815 |
+ decreasing = decreasing |
|
816 |
+ ) |
|
817 |
+ return(g) |
|
818 |
+ }) |
|
828 | 819 |
|
829 | 820 |
|
830 | 821 |
.plotDimReduceModule <- function(dim1, |
831 |
- dim2, |
|
832 |
- factorized, |
|
833 |
- modules, |
|
834 |
- rescale, |
|
835 |
- limits, |
|
836 |
- size, |
|
837 |
- xlab, |
|
838 |
- ylab, |
|
839 |
- colorLow, |
|
840 |
- colorHigh, |
|
841 |
- ncol, |
|
842 |
- decreasing) { |
|
843 |
- |
|
844 |
- matrix <- factorized$proportions$cell |
|
845 |
- |
|
846 |
- if (rescale == TRUE) { |
|
847 |
- for (x in seq(nrow(matrix))) { |
|
848 |
- matrix[x, ] <- matrix[x, ] - min(matrix[x, ]) |
|
849 |
- matrix[x, ] <- matrix[x, ] / max(matrix[x, ]) |
|
850 |
- varLabel <- "Scaled Probability" |
|
851 |
- } |
|
852 |
- } else { |
|
853 |
- varLabel <- "Probability" |
|
822 |
+ dim2, |
|
823 |
+ factorized, |
|
824 |
+ modules, |
|
825 |
+ rescale, |
|
826 |
+ limits, |
|
827 |
+ size, |
|
828 |
+ xlab, |
|
829 |
+ ylab, |
|
830 |
+ colorLow, |
|
831 |
+ colorHigh, |
|
832 |
+ ncol, |
|
833 |
+ decreasing) { |
|
834 |
+ matrix <- factorized$proportions$cell |
|
835 |
+ |
|
836 |
+ if (rescale == TRUE) { |
|
837 |
+ for (x in seq(nrow(matrix))) { |
|
838 |
+ matrix[x, ] <- matrix[x, ] - min(matrix[x, ]) |
|
839 |
+ matrix[x, ] <- matrix[x, ] / max(matrix[x, ]) |
|
840 |
+ varLabel <- "Scaled Probability" |
|
854 | 841 |
} |
842 |
+ } else { |
|
843 |
+ varLabel <- "Probability" |
|
844 |
+ } |
|
855 | 845 |
|
856 |
- rownames(matrix) <- gsub("L", "", rownames(matrix)) |
|
857 |
- if (!is.null(modules)) { |
|
858 |
- if (length(rownames(matrix)[rownames(matrix) %in% modules]) < 1) { |
|
859 |
- stop("All modules selected do not exist in the model.") |
|
860 |
- } |
|
861 |
- matrix <- matrix[which(rownames(matrix) %in% modules), , drop = FALSE] |
|
862 |
- matrix <- matrix[match(rownames(matrix), modules), , drop = FALSE] |
|
846 |
+ rownames(matrix) <- gsub("L", "", rownames(matrix)) |
|
847 |
+ if (!is.null(modules)) { |
|
848 |
+ if (length(rownames(matrix)[rownames(matrix) %in% modules]) < 1) { |
|
849 |
+ stop("All modules selected do not exist in the model.") |
|
863 | 850 |
} |
851 |
+ matrix <- |
|
852 |
+ matrix[which(rownames(matrix) %in% modules), , drop = FALSE] |
|
853 |
+ matrix <- |
|
854 |
+ matrix[match(rownames(matrix), modules), , drop = FALSE] |
|
855 |
+ } |
|
864 | 856 |
|
865 |
- rownames(matrix) <- paste0("L", rownames(matrix)) |
|
857 |
+ rownames(matrix) <- paste0("L", rownames(matrix)) |
|
866 | 858 |
|
867 |
- df <- data.frame(dim1, dim2, t(as.data.frame(matrix)), check.names = FALSE) |
|
868 |
- naIx <- is.na(dim1) | is.na(dim2) |
|
869 |
- df <- df[!naIx, ] |
|
859 |
+ df <- |
|
860 |
+ data.frame(dim1, dim2, t(as.data.frame(matrix)), check.names = FALSE) |
|
861 |
+ naIx <- is.na(dim1) | is.na(dim2) |
|
862 |
+ df <- df[!naIx, ] |
|
870 | 863 |
|
871 |
- m <- reshape2::melt(df, id.vars = c("dim1", "dim2")) |
|
872 |
- colnames(m) <- c(xlab, ylab, "facet", "Expression") |
|
864 |
+ m <- reshape2::melt(df, id.vars = c("dim1", "dim2")) |
|
865 |
+ colnames(m) <- c(xlab, ylab, "facet", "Expression") |
|
873 | 866 |
|
874 |
- if (!is.null(decreasing)) { |
|
875 |
- m <- m[order(m$facet, m$Expression, decreasing = decreasing), ] |
|
876 |
- } |
|
867 |
+ if (!is.null(decreasing)) { |
|
868 |
+ m <- m[order(m$facet, m$Expression, decreasing = decreasing), ] |
|
869 |
+ } |
|
877 | 870 |
|
878 |
- g <- ggplot2::ggplot(m, ggplot2::aes_string(x = xlab, y = ylab)) + |
|
879 |
- ggplot2::geom_point(stat = "identity", |
|
880 |
- size = size, |
|
881 |
- ggplot2::aes_string(color = m$Expression)) + |
|
882 |
- ggplot2::facet_wrap(~facet) + |
|
883 |
- ggplot2::theme_bw() + |
|
884 |
- ggplot2::scale_colour_gradient(limits = limits, |
|
885 |
- low = colorLow, |
|
886 |
- high = colorHigh, |
|
887 |
- name = varLabel) + |
|
888 |
- ggplot2::theme(strip.background = ggplot2::element_blank(), |
|
889 |
- panel.grid.major = ggplot2::element_blank(), |
|
890 |
- panel.grid.minor = ggplot2::element_blank(), |
|
891 |
- panel.spacing = unit(0, "lines"), |
|
892 |
- panel.background = ggplot2::element_blank(), |
|
893 |
- axis.line = ggplot2::element_line(colour = "black")) |
|
894 |
- if (isFALSE(is.null(ncol))) { |
|
895 |
- g <- g + ggplot2::facet_wrap(~facet, ncol = ncol) |
|
896 |
- } else { |
|
897 |
- g <- g + ggplot2::facet_wrap(~facet) |
|
898 |
- } |
|
871 |
+ g <- |
|
872 |
+ ggplot2::ggplot(m, ggplot2::aes_string(x = xlab, y = ylab)) + |
|
873 |
+ ggplot2::geom_point(stat = "identity", |
|
874 |
+ size = size, |
|
875 |
+ ggplot2::aes_string(color = m$Expression)) + |
|
876 |
+ ggplot2::facet_wrap(~ facet) + |
|
877 |
+ ggplot2::theme_bw() + |
|
878 |
+ ggplot2::scale_colour_gradient( |
|
879 |
+ limits = limits, |
|
880 |
+ low = colorLow, |
|
881 |
+ high = colorHigh, |
|
882 |
+ name = varLabel |
|
883 |
+ ) + |
|
884 |
+ ggplot2::theme( |
|
885 |
+ strip.background = ggplot2::element_blank(), |
|
886 |
+ panel.grid.major = ggplot2::element_blank(), |
|
887 |
+ panel.grid.minor = ggplot2::element_blank(), |
|
888 |
+ panel.spacing = unit(0, "lines"), |
|
889 |
+ panel.background = ggplot2::element_blank(), |
|
890 |
+ axis.line = ggplot2::element_line(colour = "black") |
|
891 |
+ ) |
|
892 |
+ if (isFALSE(is.null(ncol))) { |
|
893 |
+ g <- g + ggplot2::facet_wrap(~ facet, ncol = ncol) |
|
894 |
+ } else { |
|
895 |
+ g <- g + ggplot2::facet_wrap(~ facet) |
|
896 |
+ } |
|
899 | 897 |
|
900 |
- return(g) |
|
898 |
+ return(g) |
|
901 | 899 |
} |
902 | 900 |
|
903 | 901 |
|
... | ... |
@@ -945,19 +943,20 @@ setMethod("plotDimReduceModule", |
945 | 943 |
#' @importFrom ggrepel geom_text_repel |
946 | 944 |
#' @export |
947 | 945 |
setGeneric("plotDimReduceCluster", |
948 |
- function(x, |
|
949 |
- reducedDimName, |
|
950 |
- altExpName = "featureSubset", |
|
951 |
- dim1 = NULL, |
|
952 |
- dim2 = NULL, |
|
953 |
- size = 0.5, |
|
954 |
- xlab = NULL, |
|
955 |
- ylab = NULL, |
|
956 |
- specificClusters = NULL, |
|
957 |
- labelClusters = FALSE, |
|
958 |
- groupBy = NULL, |
|
959 |
- labelSize = 3.5) { |
|
960 |
- standardGeneric("plotDimReduceCluster")}) |
|
946 |
+ function(x, |
|
947 |
+ reducedDimName, |
|
948 |
+ altExpName = "featureSubset", |
|
949 |
+ dim1 = NULL, |
|
950 |
+ dim2 = NULL, |
|
951 |
+ size = 0.5, |
|
952 |
+ xlab = NULL, |
|
953 |
+ ylab = NULL, |
|
954 |
+ specificClusters = NULL, |
|
955 |
+ labelClusters = FALSE, |
|
956 |
+ groupBy = NULL, |
|
957 |
+ labelSize = 3.5) { |
|
958 |
+ standardGeneric("plotDimReduceCluster") |
|
959 |
+ }) |
|
961 | 960 |
|