Skip to content

Commit

Permalink
Sanitize NULL values for search result processing (#18)
Browse files Browse the repository at this point in the history
Added unit test coverage for null handling scenario.
  • Loading branch information
Gcolon021 authored Dec 4, 2024
1 parent 36d250b commit e6cae3c
Show file tree
Hide file tree
Showing 2 changed files with 88 additions and 12 deletions.
30 changes: 18 additions & 12 deletions R/bdc.R
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,12 @@ initializeGenomicAnnotations <- function(session) {

# Maps the search results to a more user friendly format, which is valid to be turned into a data frame
projectAndFilterResults = function(results, scopes, showAll) {
# Replace NULL values with an empty string for string fields
sanitize <- function(value) {
if (is.null(value)) return("")
return(value)
}

scopes = if (is.null(scopes)) c() else stringr::str_replace_all(scopes[str_detect(scopes, "^\\\\")], "\\\\", "")
in_scope = function(study) Reduce(function(acc, scope) (acc | stringr::str_detect(study, fixed(scope))), scopes, init=FALSE)

Expand All @@ -158,21 +164,21 @@ projectAndFilterResults = function(results, scopes, showAll) {

paths <- c(paths, resultMetadata$columnmeta_HPDS_PATH)
results[[index]] <- list(
name = resultMetadata$columnmeta_HPDS_PATH,
var_id = resultMetadata$derived_var_id,
var_name = resultMetadata$derived_var_name,
var_description = resultMetadata$derived_var_description,
data_type = resultMetadata$columnmeta_data_type,
group_id = resultMetadata$derived_group_id,
group_name = resultMetadata$derived_group_name,
group_description = resultMetadata$derived_group_description,
study_id = resultMetadata$derived_study_id,
study_description = resultMetadata$derived_study_description,
is_stigmatized = resultMetadata$is_stigmatized,
name = sanitize(resultMetadata$columnmeta_HPDS_PATH),
var_id = sanitize(resultMetadata$derived_var_id),
var_name = sanitize(resultMetadata$derived_var_name),
var_description = sanitize(resultMetadata$derived_var_description),
data_type = sanitize(resultMetadata$columnmeta_data_type),
group_id = sanitize(resultMetadata$derived_group_id),
group_name = sanitize(resultMetadata$derived_group_name),
group_description = sanitize(resultMetadata$derived_group_description),
study_id = sanitize(resultMetadata$derived_study_id),
study_description = sanitize(resultMetadata$derived_study_description),
is_stigmatized = sanitize(resultMetadata$is_stigmatized),
min = if (categorical) NA else as.numeric(resultMetadata$columnmeta_min),
max = if (categorical) NA else as.numeric(resultMetadata$columnmeta_max),
categorical = categorical,
values = toString(results[[index]]$result$values)
values = sanitize(toString(results[[index]]$result$values))
)
include_list <- c(include_list, index)
}
Expand Down
70 changes: 70 additions & 0 deletions tests/testthat/test-bdc.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
source("../../R/bdc.R", chdir = TRUE)
library(testthat)

test_that("projectAndFilterResults handles nulls and in-scope results correctly", {
# Mock input data
mockResults <- list(
list(result = list(
metadata = list(
columnmeta_HPDS_PATH = "\\phs000001\\unit_test\\test_categorical_variable\\",
derived_var_id = "var1",
derived_var_name = NULL, # Should be converted to ""
derived_var_description = NULL, # Should be converted to ""
columnmeta_data_type = "categorical",
derived_group_id = "group1",
derived_group_name = NULL, # Should be converted to ""
derived_group_description = "desc1",
derived_study_id = "study1",
derived_study_description = NULL, # Should be converted to ""
is_stigmatized = NULL, # Should be converted to ""
columnmeta_min = NULL,
columnmeta_max = NULL
),
is_categorical = TRUE,
values = NULL # Should be converted to ""
)),
list(result = list(
metadata = list(
columnmeta_HPDS_PATH = "\\phs000001\\unit_test\\test_continuous_variable\\",
derived_var_id = "var2",
derived_var_name = "Test Continuous Variable",
derived_var_description = "A test continuous variable",
columnmeta_data_type = "continuous",
derived_group_id = "group2",
derived_group_name = "Test Group",
derived_group_description = "A description for group 2",
derived_study_id = "study2",
derived_study_description = "Study 2 Description",
is_stigmatized = "false",
columnmeta_min = "1.1",
columnmeta_max = "42"
),
is_categorical = FALSE,
values = "" # Should remain unchanged
))
)

mockScopes <- c("phs000001")
mockShowAll <- TRUE

# Run the function
result <- projectAndFilterResults(mockResults, mockScopes, mockShowAll)

expect_true(length(result$results) > 0, info = "No results returned; check input data or filtering logic.")

# Verify results structure
expect_true(is.list(result))
expect_named(result, c("results", "paths"))

# Verify paths
expect_equal(result$paths, c("\\phs000001\\unit_test\\test_categorical_variable\\", "\\phs000001\\unit_test\\test_continuous_variable\\"))

expect_equal(result$results[[1]]$var_name, "") # NULL replaced with ""
expect_equal(result$results[[1]]$min, NA) # Categorical, so NA
expect_equal(result$results[[1]]$categorical, TRUE)

expect_equal(result$results[[2]]$name, "\\phs000001\\unit_test\\test_continuous_variable\\")
expect_equal(result$results[[2]]$min, 1.1) # Converted to numeric
expect_equal(result$results[[2]]$max, 42) # Converted to numeric
expect_equal(result$results[[2]]$categorical, FALSE)
})

0 comments on commit e6cae3c

Please sign in to comment.