Skip to content

Commit 06e5aa4

Browse files
committed
Merge branch 'devel'
Include bug fixes and changes to output from `calculateConcordex()`. Also changes approach to serial evaluation
2 parents 5222135 + 4c8e8f6 commit 06e5aa4

File tree

5 files changed

+46
-30
lines changed

5 files changed

+46
-30
lines changed

DESCRIPTION

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Package: concordexR
22
Title: Identify Spatial Homogeneous Regions with concordex
3-
Version: 1.9.0
3+
Version: 1.9.1
44
Authors@R: c(
55
person("Kayla", "Jackson", , "[email protected]", role = c("aut", "cre"),
66
comment = c(ORCID = "0000-0001-6483-0108")),
@@ -31,7 +31,7 @@ URL: https://github.com/pachterlab/concordexR,
3131
https://pachterlab.github.io/concordexR/
3232
BugReports: https://github.com/pachterlab/concordexR/issues
3333
Depends:
34-
R (>= 4.4.0)
34+
R (>= 4.5.0)
3535
Imports:
3636
BiocGenerics,
3737
BiocNeighbors,

R/concordex-internals.R

Lines changed: 26 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -30,21 +30,29 @@
3030
check_dots_empty()
3131
dims <- dim(g)
3232

33-
34-
# The graph is dense, so we can get some improvements on mapping
33+
# The index is dense, so we can get some improvements
3534
# by converting to a list of rows
36-
g <- pmap(data.frame(g), c)
35+
g <- split(g, seq(dims[1]))
3736

38-
nbc <- bplapply(g, function(rows) {
39-
nbx <- colMeans2(labels, rows=rows)
40-
as(nbx,"sparseMatrix")},
41-
BPPARAM=BPPARAM)
37+
nw <- BPPARAM$workers
4238

43-
nbc <- do.call(cbind, nbc)
39+
.consolidate <- function(rows) {
40+
mapply(FUN=function(r){colMeans2(labels, rows=r)}, rows, SIMPLIFY=FALSE)
41+
}
4442

45-
# Transpose so that labels are on columns
46-
t(nbc)
43+
if (nw <= 1L) {
44+
# Avoid `bplappy()` for serial
45+
nbc <- .consolidate(g)
46+
nbc <- do.call(rbind, nbc)
4747

48+
} else {
49+
nbc <- bpvec(g, .consolidate,
50+
AGGREGATE = function(...) do.call(rbind, c(...)),
51+
BPPARAM=BPPARAM)
52+
}
53+
# Transpose so that labels are on columns
54+
# t(nbc)
55+
nbc
4856
}
4957

5058
.concordex_stat <- function(nbc, labels, n_neighbors) {
@@ -95,23 +103,26 @@
95103

96104
# Compute for each row(/cell/spot) in g
97105
nbc <- .concordex_nbhd_consolidation(g, labels, BPPARAM=BPPARAM)
106+
out <- list("NBC"=nbc)
98107

99108
if (cluster_neighborhoods & !missing(BLUSPARAM)) {
100109
if (class(BLUSPARAM) %in% "MbkmeansParam") {
101110
shr <- clusterRows(as.matrix(nbc), BLUSPARAM=BLUSPARAM)
102111
} else {
103-
shr <- clusterRows(nbc, BLUSPARAM=BLUSPARAM)
112+
shr <- clusterRows(nbc, BLUSPARAM=BLUSPARAM, full=FALSE)
104113
}
105114

106-
attr(nbc, "shrs") <- shr
115+
out[['SHR']] <- shr
107116
}
108117

109118
if (compute_similarity) {
110119
# statistics
111120
cdx <- .concordex_stat(nbc, labels, n_neighbors=n_neighbors)
112-
attr(nbc, "similarity") <- cdx$similarity
113-
attr(nbc, "concordex") <- cdx$concordex
121+
122+
out[["SIMILARITY"]] <- cdx$similarity
123+
out[["CONCORDEX_SCORE"]] <- cdx$concordex
124+
114125
}
115126

116-
nbc
127+
out
117128
}

R/concordex.R

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -46,8 +46,8 @@
4646
#' parallelized (see \code{\link{bpparam}}).
4747
#'
4848
#' @return
49-
#' For \code{calculateConcordex}, a sparse, numeric matrix representing the
50-
#' neighborhood consolidation for each cell (row)
49+
#' For \code{calculateConcordex}, A list containing a sparse, numeric matrix representing the
50+
#' neighborhood consolidation for each cell (row) and SHR identities.
5151
#'
5252
#' For \code{runConcordex}, a SingleCellExperiment (or SpatialExperiment) object
5353
#' is returned containing this matrix in \code{\link{reducedDims}(..., name)}.
@@ -92,8 +92,8 @@ setMethod("calculateConcordex", "ANY",
9292
...,
9393
n_neighbors=30,
9494
compute_similarity=FALSE,
95-
BLUSPARAM,
9695
BNINDEX,
96+
BLUSPARAM=NNGraphParam(cluster.fun="louvain"),
9797
BNPARAM=KmknnParam(),
9898
BPPARAM=SerialParam()) {
9999

@@ -154,7 +154,7 @@ setMethod("calculateConcordex", "SummarizedExperiment",
154154
#' @param ... Other parameters passed to default method
155155
#' @param use.dimred Integer or string specifying the reduced dimensions to use
156156
#' for construction of the k-nearest neighbor graph. Note that if this is not
157-
#' \code{NULL}, reduced dimensions can not be used as labels to compute the
157+
#' \code{NULL}, reduced dimensions cannot be used as labels to compute the
158158
#' neighborhood consolidation matrix.
159159
#'
160160
#' @export
@@ -204,10 +204,10 @@ setMethod("runConcordex", "SpatialExperiment", function(x, labels, ..., name="NB
204204
{
205205
nbc <- calculateConcordex(x, labels, ...)
206206

207-
if ("shrs" %in% names(attrs(nbc))) {
208-
colData["shr"] <- attrs(nbc)$shrs
207+
if ("SHR" %in% names(nbc)) {
208+
colData["shr"] <- nbc[["SHR"]]
209209
}
210-
reducedDim(x, name) <- nbc
210+
reducedDim(x, name) <- nbc[["NBC"]]
211211

212212
x
213213
})
@@ -217,7 +217,7 @@ setMethod("runConcordex", "SpatialExperiment", function(x, labels, ..., name="NB
217217
#' @rdname calculateConcordex
218218
setMethod("runConcordex", "SingleCellExperiment", function(x, labels, ..., name="NBC")
219219
{
220-
reducedDim(x, name) <- calculateConcordex(x, labels, ...)
221-
220+
nbc <- calculateConcordex(x, labels, ...)
221+
reducedDim(x, name) <- nbc[["NBC"]]
222222
x
223223
})

man/calculateConcordex.Rd

Lines changed: 8 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

vignettes/concordex-nonspatial.Rmd

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -187,7 +187,7 @@ the proportion of cells with each label in the neighborhood of other cells with
187187
same label.
188188

189189
```{r}
190-
sim <- attr(res, "similarity")
190+
sim <- res[["SIMILARITY"]]
191191
192192
round(sim, 2)
193193
```

0 commit comments

Comments
 (0)