Skip to content

Commit

Permalink
Issue #70: Status code changed from 500 to 400. Added current_status …
Browse files Browse the repository at this point in the history
…tests.
  • Loading branch information
salatak committed Feb 28, 2024
1 parent 6cd8b92 commit 694affe
Show file tree
Hide file tree
Showing 2 changed files with 91 additions and 2 deletions.
38 changes: 38 additions & 0 deletions R/api_randomize.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,44 @@ api__randomize_patient <- function(study_id, current_state, req, res) {
add = collection
)

browser()

checkmate::assert(
checkmate::check_data_frame(current_state,
any.missing = TRUE,
all.missing = FALSE, nrows = 2, ncols = 3
),
.var.name = "current_state",
add = collection
)

checkmate::assert(
checkmate::check_names(
colnames(current_state),
must.include = "arm"
),
.var.name = "current_state",
add = collection
)


check_arm <- function(x) {
res <- checkmate::check_character(
current_state$arm[nrow(current_state)],
max.chars = 0
)
if (!isTRUE(res)) {
res <- ("Last value should be empty")
}
return(res)
}

checkmate::assert(
check_arm(),
.var.name = "current_state[arm]",
add = collection
)

if (length(collection$getMessages()) > 0) {
res$status <- 400
return(list(
Expand Down
55 changes: 53 additions & 2 deletions tests/testthat/test-E2E-study-minimisation-pocock.R
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,7 @@ test_that("request with patient that is assigned an arm at entry", {
response |>
resp_body_json()

response_current_state <-
response_cs_arm <-
tryCatch(
{
request(api_url) |>
Expand All @@ -220,7 +220,58 @@ test_that("request with patient that is assigned an arm at entry", {
)

testthat::expect_equal(
response_current_state$status, 500,
response_cs_arm$status, 400,
label = "HTTP status code"
)

response_cs_records <-
tryCatch(
{
request(api_url) |>
req_url_path("study", response_body$study$id, "patient") |>
req_method("POST") |>
req_body_json(
data = list(
current_state =
tibble::tibble(
"sex" = c("female"),
"weight" = c("61-80 kg"),
"arm" = c("placebo")
)
)
) |>
req_perform()
},
error = function(e) e
)

testthat::expect_equal(
response_cs_records$status, 400,
label = "HTTP status code"
)

response_current_state <-
tryCatch(
{
request(api_url) |>
req_url_path("study", response_body$study$id, "patient") |>
req_method("POST") |>
req_body_json(
data = list(
current_state =
tibble::tibble(
"sex" = c("female", "male"),
"weight" = c("61-80 kg", "81 kg or more")
)
)
) |>
req_perform()
},
error = function(e) e
)

testthat::expect_equal(
response_current_state$status, 400,
label = "HTTP status code"
)
})
Expand Down

0 comments on commit 694affe

Please sign in to comment.