Skip to content

Commit

Permalink
Merge pull request #93 from ttscience/fix-too-aggressive-current-stat…
Browse files Browse the repository at this point in the history
…e-validation

Fix too aggressive current state validation in randomization endpoint
  • Loading branch information
lwalejko authored Mar 26, 2024
2 parents 1528495 + 1bbcce3 commit f67c82c
Show file tree
Hide file tree
Showing 3 changed files with 78 additions and 3 deletions.
2 changes: 1 addition & 1 deletion R/api_randomize.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ api__randomize_patient <- function(study_id, current_state, req, res) {
checkmate::assert(
checkmate::check_data_frame(current_state,
any.missing = TRUE,
all.missing = FALSE, nrows = 2, ncols = 3
all.missing = FALSE, min.rows = 1
),
.var.name = "current_state",
add = collection
Expand Down
75 changes: 74 additions & 1 deletion tests/testthat/test-E2E-study-minimisation-pocock.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ test_that("correct request with the structure of the returned result", {
response_patient |>
resp_body_json()

testthat::expect_equal(response$status_code, 200)
testthat::expect_equal(response_patient$status_code, 200)
checkmate::expect_number(response_patient_body$patient_id, lower = 1)

# Endpoint Response Structure Test
Expand Down Expand Up @@ -502,3 +502,76 @@ test_that("request with incorrect ratio", {

testthat::expect_equal(response_ratio$status, 400)
})

test_that("randomization works for 1 patient", {
with_db_fixtures("fixtures/example_db.yml")
response_patient <- request(api_url) |>
req_url_path("study", "1", "patient") |>
req_method("POST") |>
req_error(is_error = \(x) FALSE) |>
req_body_json(
data = list(
current_state =
tibble::tibble(
"gender" = c("F"),
"arm" = c("")
)
)
) |>
req_perform()

response_patient_body <-
response_patient |>
resp_body_json()

testthat::expect_equal(response_patient$status_code, 200)
checkmate::expect_number(response_patient_body$patient_id, lower = 1)
})
test_that("randomization works for 2 patients", {
with_db_fixtures("fixtures/example_db.yml")
response_patient <- request(api_url) |>
req_url_path("study", "1", "patient") |>
req_method("POST") |>
req_error(is_error = \(x) FALSE) |>
req_body_json(
data = list(
current_state =
tibble::tibble(
"gender" = c("F", "M"),
"arm" = c("placebo", "")
)
)
) |>
req_perform()

response_patient_body <-
response_patient |>
resp_body_json()

testthat::expect_equal(response_patient$status_code, 200)
checkmate::expect_number(response_patient_body$patient_id, lower = 1)
})
test_that("randomization works for 3 patients", {
with_db_fixtures("fixtures/example_db.yml")
response_patient <- request(api_url) |>
req_url_path("study", "1", "patient") |>
req_method("POST") |>
req_error(is_error = \(x) FALSE) |>
req_body_json(
data = list(
current_state =
tibble::tibble(
"gender" = c("F", "M", "F"),
"arm" = c("placebo", "active", "")
)
)
) |>
req_perform()

response_patient_body <-
response_patient |>
resp_body_json()

testthat::expect_equal(response_patient$status_code, 200)
checkmate::expect_number(response_patient_body$patient_id, lower = 1)
})
4 changes: 3 additions & 1 deletion tests/testthat/test-api-audit-log.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,9 @@ testthat::test_that("audit logs for study are returned correctly from the databa
testthat::expect_identical(response$status_code, 200L)
testthat::expect_identical(length(response_body), count)

created_at <- response_body |> dplyr::bind_rows() |> dplyr::pull("created_at")
created_at <- response_body |>
dplyr::bind_rows() |>
dplyr::pull("created_at")
testthat::expect_equal(
created_at,
created_at |> sort()
Expand Down

0 comments on commit f67c82c

Please sign in to comment.