Skip to content

Commit

Permalink
Add test
Browse files Browse the repository at this point in the history
Signed-off-by: cosa65 <[email protected]>
  • Loading branch information
cosa65 committed Nov 16, 2023
1 parent f0eb710 commit f1631db
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 18 deletions.
6 changes: 3 additions & 3 deletions pipeline-runner/R/qc-7-embed_and_cluster.R
Original file line number Diff line number Diff line change
Expand Up @@ -388,14 +388,14 @@ make_cl_metadata_cellclass <- function(variable, type, cl_metadata, color_pool)

cell_ids <- cl_metadata[get(variable) == values[i] & cl_metadata$duplicate_barcode == "no", cells_id]

# Empty cell sets shouldn't be created based on cell level metadata
if (length(cell_ids) == 0) next

# do not add duplicate barcodes, except for the duplicate_barcode cellset
if (variable == "duplicate_barcode") {
cell_ids <- cl_metadata[get(variable) == values[i], cells_id]
}

# Empty cell sets shouldn't be created based on cell level metadata
if (length(cell_ids) == 0) next

cl_metadata_cellset$children <- append(
cl_metadata_cellset$children,
list(
Expand Down
18 changes: 3 additions & 15 deletions pipeline-runner/tests/testthat/test-qc-7-embed_and_cluster.R
Original file line number Diff line number Diff line change
Expand Up @@ -613,27 +613,16 @@ test_that("make_cl_metadata_cellsets skips making cellsets that are empty (no ce
scdata <- mock_scdata()
cl_metadata <- mock_cl_metadata(
scdata,
c(rownames(scdata@meta.data), paste0(barcode, 1:50))
c(paste0("missing-barcode", 1:50))
)

local_mock_cl_metadata_table(cl_metadata, "mock_experiment_id")

res <- stubbed_make_cl_metadata_cellsets(scdata, config)
withr::defer(unlink(file.path(".", basename(config$metadata_s3_path))))

expect_equal(length(res), 4)
expect_equal(length(res[[1]]$children), length(unique(cl_metadata$cell_type)))
expect_equal(length(res[[2]]$children), 1)
expect_equal(length(res[[3]]$children), length(unique(cl_metadata$group_var)))
expect_equal(length(res[[4]]$children), length(unique(cl_metadata$redundant_group_var)))

cell_class_names <- c("key", "name", "rootNode", "type", "children")
purrr::walk(res, expect_named, cell_class_names)

# cellsets have the same keys as cell classes except children, color and cellIds
for (i in seq_along(res)) {
purrr::walk(res[[i]]$children, expect_named, c(cell_class_names[-5], "color", "cellIds"))
}
expect_equal(length(res[[1]]$children), 0)
expect_equal(length(res[[2]]$children), 0)
})


Expand Down Expand Up @@ -664,7 +653,6 @@ test_that("make_cl_metadata_table works with duplicate barcodes", {

expect_equal(length(res), 4)
expect_equal(length(res[[1]]$children), length(unique(cl_metadata$cell_type)))

expect_equal(length(res[[2]]$children), 2)
expect_equal(length(res[[3]]$children), length(unique(cl_metadata$group_var)))
expect_equal(length(res[[4]]$children), length(unique(cl_metadata$redundant_group_var)))
Expand Down

0 comments on commit f1631db

Please sign in to comment.