Skip to content

Commit

Permalink
[r] add get_seurat() (#293)
Browse files Browse the repository at this point in the history
Add `get_seurat()` analogous to `get_anndata()` in Python, and port the test cases as well.
  • Loading branch information
mlin authored Mar 28, 2023
1 parent fa67b72 commit 01691ef
Show file tree
Hide file tree
Showing 6 changed files with 157 additions and 3 deletions.
3 changes: 2 additions & 1 deletion api/r/CellCensus/DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,8 @@ Imports:
stats,
tiledbsoma,
tiledb
Suggests:
Suggests:
bit64,
knitr,
rmarkdown,
testthat (>= 3.0.0),
Expand Down
2 changes: 2 additions & 0 deletions api/r/CellCensus/NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ export(download_source_h5ad)
export(get_census_version_description)
export(get_census_version_directory)
export(get_presence_matrix)
export(get_seurat)
export(get_source_h5ad_uri)
export(open_soma)
importFrom(aws.s3,save_object)
Expand All @@ -13,4 +14,5 @@ importFrom(jsonlite,fromJSON)
importFrom(methods,is)
importFrom(stats,setNames)
importFrom(tiledbsoma,SOMACollection)
importFrom(tiledbsoma,SOMAExperimentAxisQuery)
importFrom(tiledbsoma,SOMATileDBContext)
42 changes: 41 additions & 1 deletion api/r/CellCensus/R/get_helpers.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
#' Read the feature dataset presence matrix.
#'
#' @param census The census SOMACollection from which to read the presence matrix.
#' @param census The census object, usually returned by `CellCensus::open_soma()`.
#' @param organism The organism to query, usually one of `Homo sapiens` or `Mus musculus`
#' @param measurement_name The measurement object to query. Defaults to `RNA`.
#'
Expand All @@ -15,6 +15,46 @@ get_presence_matrix <- function(census, organism, measurement_name = "RNA") {
return(presence$read_sparse_matrix())
}

#' Convenience wrapper around `SOMAExperimentAxisQuery`, to build and execute a
#' query, and return it as a `Seurat` object.
#'
#' @param census The census object, usually returned by `CellCensus::open_soma()`.
#' @param organism The organism to query, usually one of `Homo sapiens` or `Mus musculus`
#' @param measurement_name The measurement object to query. Defaults to `RNA`.
#' @param X_name The `X` layer to query. Defaults to `raw`.
#' @param obs_query A `SOMAAxisQuery` for the `obs` axis.
#' @param obs_column_names Columns to fetch for the `obs` data frame.
#' @param var_query A `SOMAAxisQuery` for the `var` axis.
#' @param var_column_names Columns to fetch for the `var` data frame.
#'
#' @return A `Seurat` object containing the sensus slice.
#' @importFrom tiledbsoma SOMAExperimentAxisQuery
#' @export
#'
#' @examples
get_seurat <- function(
census,
organism,
measurement_name = "RNA",
X_name = "raw",
obs_query = NULL,
obs_column_names = NULL,
var_query = NULL,
var_column_names = NULL) {
expt_query <- tiledbsoma::SOMAExperimentAxisQuery$new(
get_experiment(census, organism),
measurement_name,
obs_query = obs_query,
var_query = var_query
)
return(expt_query$to_seurat(
# TODO: should we allow selection of the seurat 'counts' or 'data' slot?
c(counts = X_name),
obs_column_names = obs_column_names,
var_column_names = var_column_names
))
}

#' Get the SOMAExperiment for a named organism
#'
#' @param census The census SOMACollection.
Expand Down
2 changes: 1 addition & 1 deletion api/r/CellCensus/man/get_presence_matrix.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

42 changes: 42 additions & 0 deletions api/r/CellCensus/man/get_seurat.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

69 changes: 69 additions & 0 deletions api/r/CellCensus/tests/testthat/test-get_helpers.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,3 +31,72 @@ test_that("get_presence_matrix", {
expect_equal(max(pm), 1)
}
})

test_that("get_seurat", {
seurat <- get_seurat(
open_soma(),
"Mus musculus",
obs_query = tiledbsoma::SOMAAxisQuery$new(value_filter = "tissue_general == 'vasculature'"),
obs_column_names = c("soma_joinid", "cell_type", "tissue", "tissue_general", "assay"),
var_query = tiledbsoma::SOMAAxisQuery$new(value_filter = "feature_name %in% c('Gm53058', '0610010K14Rik')"),
var_column_names = c("soma_joinid", "feature_id", "feature_name", "feature_length")
)

expect_s4_class(seurat, "Seurat")
seurat_assay <- seurat[["RNA"]]
expect_s4_class(seurat_assay, "Assay")
expect_equal(nrow(seurat_assay), 2)
expect_gt(ncol(seurat_assay), 0)
expect_setequal(seurat_assay[[]][, "feature_name"], c("0610010K14Rik", "Gm53058"))
expect_equal(sum(seurat[[]][, "tissue_general"] == "vasculature"), ncol(seurat_assay))
})

test_that("get_seurat coords", {
seurat <- get_seurat(
open_soma(),
"Mus musculus",
obs_query = tiledbsoma::SOMAAxisQuery$new(
coords = list(soma_joinid = bit64::as.integer64(0:1000))
),
var_query = tiledbsoma::SOMAAxisQuery$new(
coords = list(soma_joinid = bit64::as.integer64(0:2000))
)
)
expect_equal(nrow(seurat[[]]), 1001) # obs dataframe
seurat_assay <- seurat[["RNA"]]
expect_equal(nrow(seurat_assay[[]]), 2001) # var dataframe
# NOTE: seurat assay matrix is var x obs, not obs x var
expect_equal(nrow(seurat_assay), 2001)
expect_equal(ncol(seurat_assay), 1001)
})

test_that("get_seurat allows missing obs or var filter", {
census <- open_soma()

obs_query <- tiledbsoma::SOMAAxisQuery$new(
value_filter = "tissue == 'aorta'"
)
seurat <- get_seurat(census, "Mus musculus",
obs_query = obs_query,
obs_column_names = c("soma_joinid"),
var_column_names = c("soma_joinid")
)
control_query <- tiledbsoma::SOMAExperimentAxisQuery$new(
get_experiment(census, "Mus musculus"),
"RNA",
obs_query = obs_query
)
expect_equal(ncol(seurat[["RNA"]]), control_query$n_obs)
expect_equal(nrow(seurat[["RNA"]]), control_query$n_vars)

seurat <- get_seurat(census, "Mus musculus",
obs_query = tiledbsoma::SOMAAxisQuery$new(
coords = list(soma_joinid = bit64::as.integer64(0:10000))
),
var_query = tiledbsoma::SOMAAxisQuery$new(
value_filter = "feature_id == 'ENSMUSG00000069581'"
)
)
expect_equal(ncol(seurat[["RNA"]]), 10001)
expect_equal(nrow(seurat[["RNA"]]), 1)
})

0 comments on commit 01691ef

Please sign in to comment.