Skip to content

Commit

Permalink
Merge pull request #133 from molgenis/fix/subset
Browse files Browse the repository at this point in the history
fix: subset
  • Loading branch information
timcadman authored Jun 27, 2024
2 parents 579faa0 + 1880b38 commit 9d17d72
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 1 deletion.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ importFrom(purrr,map_lgl)
importFrom(purrr,pmap)
importFrom(purrr,walk)
importFrom(readr,read_csv)
importFrom(stringr,str_ends)
importFrom(stringr,str_replace)
importFrom(tibble,tibble)
importFrom(tidyr,nest)
Expand Down
18 changes: 17 additions & 1 deletion R/subset.R
Original file line number Diff line number Diff line change
Expand Up @@ -304,7 +304,23 @@ armadillo.subset_definition <- function(reference_csv = NULL, vars = NULL) { # n
#' @param target_project Project to upload subset to.
#' @noRd
.make_post_url <- function(target_project) {
return(sprintf("%sstorage/projects/%s/objects/link", .get_url(), target_project))
server_url <- .add_slash_if_missing(.get_url())
return(sprintf("%sstorage/projects/%s/objects/link", server_url, target_project))
}

#' Add a Slash to a URL if Missing
#'
#' This function ensures that a given URL string ends with a slash ('/').
#' If the URL does not end with a slash, it appends one.
#'
#' @param url A character string representing the URL.
#' @return A character string with a trailing slash if it was missing.
#' @importFrom stringr str_ends
.add_slash_if_missing <- function(url) {
if(!str_ends(url, "/")) {
url <- paste0(url, "/")
}
return(url)
}

#' Creates JSON body for the API request
Expand Down
18 changes: 18 additions & 0 deletions man/dot-add_slash_if_missing.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

13 changes: 13 additions & 0 deletions tests/testthat/test-subset.R
Original file line number Diff line number Diff line change
Expand Up @@ -533,3 +533,16 @@ test_that("armadillo.subset fails if subset_def is NULL", {
fixed = TRUE
)
})

test_that(".add_slash_if_missing adds a slash to the end of the URL if not present", {
expect_equal(
.add_slash_if_missing("https://armadillo-demo.molgenis.net"),
"https://armadillo-demo.molgenis.net/"
)

expect_equal(
.add_slash_if_missing("https://armadillo-demo.molgenis.net/"),
"https://armadillo-demo.molgenis.net/"
)

})

0 comments on commit 9d17d72

Please sign in to comment.