Skip to content

Commit

Permalink
always start new session if not present
Browse files Browse the repository at this point in the history
  • Loading branch information
hillalex committed Aug 28, 2024
1 parent bd2c9b5 commit 4453d99
Show file tree
Hide file tree
Showing 4 changed files with 68 additions and 22 deletions.
20 changes: 7 additions & 13 deletions R/api.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,15 @@
target_get_root <- function() {
target_get_root <- function(req) {
get_or_create_session_id(req)
jsonlite::unbox("Welcome to serovizr")
}

target_get_version <- function() {
target_get_version <- function(req) {
get_or_create_session_id(req)
jsonlite::unbox(as.character(utils::packageVersion("serovizr")))
}

target_post_dataset <- function(req, res) {
session_id <- get_or_create_session_id(req)
logger::log_info("Parsing multipart form request")
parsed <- mime::parse_multipart(req)
xcol <- parsed$xcol
Expand All @@ -27,7 +30,6 @@ target_post_dataset <- function(req, res) {
filename <- stringr::str_remove_all(filename,
paste0(".", file_ext))
}
session_id <- get_or_create_session_id(req)
path <- file.path("uploads", session_id, filename)
if (dir.exists(path)) {
res$status <- 400L
Expand Down Expand Up @@ -80,7 +82,7 @@ target_get_dataset <- function(name, req) {
}

target_get_datasets <- function(req) {
session_id <- get_session_id(req)
session_id <- get_or_create_session_id(req)
list.files(file.path("uploads", session_id))
}

Expand Down Expand Up @@ -127,7 +129,7 @@ target_get_trace <- function(name,
}

read_dataset <- function(req, name) {
session_id <- get_session_id(req)
session_id <- get_or_create_session_id(req)
path <- file.path("uploads", session_id, name)
if (!file.exists(path)) {
porcelain::porcelain_stop(paste("Did not find dataset with name:", name),
Expand Down Expand Up @@ -188,14 +190,6 @@ get_or_create_session_id <- function(req) {
as.character(req$session$id)
}

get_session_id <- function(req) {
if (is.null(req$session$id)) {
porcelain::porcelain_stop("No session cookie present.",
code = "NO_SESSION", status_code = 401L)
}
as.character(req$session$id)
}

generate_session_id <- function() {
rawToChar(as.raw(sample(c(65:90,97:122), 10, replace=T)))

Check warning on line 194 in R/api.R

View workflow job for this annotation

GitHub Actions / lint

file=R/api.R,line=194,col=35,[commas_linter] Commas should always have a space after.

Check warning on line 194 in R/api.R

View workflow job for this annotation

GitHub Actions / lint

file=R/api.R,line=194,col=55,[infix_spaces_linter] Put spaces around all infix operators.

Check warning on line 194 in R/api.R

View workflow job for this annotation

GitHub Actions / lint

file=R/api.R,line=194,col=57,[T_and_F_symbol_linter] Use TRUE instead of the symbol T.
}
6 changes: 3 additions & 3 deletions tests/testthat/test-read.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
test_that("GET /dataset<name> returns 401 if no session cookie present", {
test_that("GET /dataset<name> returns 404 if no session cookie present", {
router <- build_routes(cookie_key)
res <- router$call(make_req("GET",
"/dataset/testdataset/"))
expect_equal(res$status, 401)
expect_equal(res$status, 404)
validate_failure_schema(res$body)
body <- jsonlite::fromJSON(res$body)
expect_equal(body$errors[1, "detail"],
"No session cookie present.")
"Did not find dataset with name: testdataset")
})

test_that("GET /dataset<name> returns 404 if dataset not found", {
Expand Down
7 changes: 4 additions & 3 deletions tests/testthat/test-router.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
test_that("GET /", {
res <- target_get_root()
mock_req <- as.environment(list(id = 1234))
res <- target_get_root(mock_req)
expect_equal(res, jsonlite::unbox("Welcome to serovizr"))

endpoint <- get_root()
res_endpoint <- endpoint$run()
res_endpoint <- endpoint$run(mock_req)
expect_equal(res_endpoint$status_code, 200)
expect_equal(res_endpoint$content_type, "application/json")
expect_equal(res_endpoint$data, res)
Expand All @@ -15,7 +16,7 @@ test_that("GET /", {
})

test_that("GET /version", {
res <- target_get_version()
res <- target_get_version(as.environment(list(id = 1234)))
expect_equal(res, jsonlite::unbox(as.character(packageVersion("serovizr"))))

router <- build_routes()
Expand Down
57 changes: 54 additions & 3 deletions tests/testthat/test-session.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ test_that("existing session id is used if present on POST /dataset", {
router <- build_routes(key)

session <- list(id = "1234")

cookie <- plumber:::cookieToStr("serovizr",
plumber:::encodeCookie(session,
plumber:::asCookieKey(key)))
Expand All @@ -41,7 +40,59 @@ test_that("existing session id is used if present on POST /dataset", {
expect_true(fs::file_exists("uploads/1234/testdataset"))
})

test_that("existing session id is used if present on GET /dataset", {
test_that("new session id is set if not present on GET /dataset", {
key <- plumber::random_cookie_key()
router <- build_routes(key)
get_request_without_cookie <- make_req("GET",
"/dataset/testdataset/")
res <- router$call(get_request_without_cookie)
cookie <- res$headers[["Set-Cookie"]]
session <- plumber:::decodeCookie(plumber:::parseCookies(cookie)[[1]],
plumber:::asCookieKey(key))
expect_true(is.character(session$id))
expect_equal(nchar(session$id), 10)
})

test_that("new session id is set if not present on GET /", {
key <- plumber::random_cookie_key()
router <- build_routes(key)
get_request_without_cookie <- make_req("GET",
"/")
res <- router$call(get_request_without_cookie)
cookie <- res$headers[["Set-Cookie"]]
session <- plumber:::decodeCookie(plumber:::parseCookies(cookie)[[1]],
plumber:::asCookieKey(key))
expect_true(is.character(session$id))
expect_equal(nchar(session$id), 10)
})

test_that("new session id is set if not present on GET /version/", {
key <- plumber::random_cookie_key()
router <- build_routes(key)
get_request_without_cookie <- make_req("GET",
"/version/")
res <- router$call(get_request_without_cookie)
cookie <- res$headers[["Set-Cookie"]]
session <- plumber:::decodeCookie(plumber:::parseCookies(cookie)[[1]],
plumber:::asCookieKey(key))
expect_true(is.character(session$id))
expect_equal(nchar(session$id), 10)
})

test_that("new session id is set if not present on GET /dataset/trace/", {
key <- plumber::random_cookie_key()
router <- build_routes(key)
set.seed(1)
get_request_without_cookie <- make_req("GET",
"/dataset/testdataset/trace/ab/")
res <- router$call(get_request_without_cookie)
cookie <- res$headers[["Set-Cookie"]]
session <- plumber:::decodeCookie(plumber:::parseCookies(cookie)[[1]],
plumber:::asCookieKey(key))
expect_equal(session$id, session_id)
})

test_that("existing session id is used if present on GET /dataset/trace/", {
key <- plumber::random_cookie_key()
router <- build_routes(key)
session <- list(id = "1234")
Expand All @@ -62,7 +113,7 @@ test_that("existing session id is used if present on GET /dataset", {
"/dataset/testdataset/trace/ab/")

res <- router$call(get_request_without_cookie)
expect_equal(res$status, 401)
expect_equal(res$status, 404)

get_request_with_cookie <- make_req("GET",
"/dataset/testdataset/trace/ab/",
Expand Down

0 comments on commit 4453d99

Please sign in to comment.