Skip to content

Commit

Permalink
up
Browse files Browse the repository at this point in the history
  • Loading branch information
TuomasBorman committed Mar 17, 2024
1 parent 30ca97e commit b216b06
Show file tree
Hide file tree
Showing 5 changed files with 28 additions and 31 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: MGnifyR
Type: Package
Version: 0.99.25
Version: 0.99.26
Authors@R:
c(person(given = "Tuomas", family = "Borman", role = c("aut", "cre"),
email = "[email protected]",
Expand Down
41 changes: 21 additions & 20 deletions R/MgnifyClient.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,12 +19,10 @@
#' (By default: \code{useCache = FALSE})
#'
#' @param cacheDir A single character value specifying a folder to contain the
#' local cache. If NULL, and useCache is TRUE, the new subdirectory
#' \code{.MGnifyR_cache} in the current working directory will be used. Note
#' that cached files are persistent, so the cache directory may be reused
#' between sessions, taking advantage of previously downloaded results. The
#' directory will be created if it doesn't exist already.
#' (By default: \code{cachedir = NULL})
#' local cache. Note that cached files are persistent, so the cache directory
#' may be reused between sessions, taking advantage of previously downloaded
#' results. The directory will be created if it doesn't exist already.
#' (By default: \code{cacheDir = tempdir()})
#'
#' @param showWarnings A single boolean value specifying whether to print
#' warnings during invocation of some MGnifyR functions.
Expand Down Expand Up @@ -66,8 +64,9 @@ NULL
#' @importFrom methods new
#' @export
MgnifyClient <- function(
username = NULL, password = NULL, useCache = FALSE, cacheDir = NULL,
showWarnings = FALSE, verbose = TRUE, clearCache = FALSE, ...){
username = NULL, password = NULL, useCache = FALSE,
cacheDir = tempdir(), showWarnings = FALSE, verbose = TRUE,
clearCache = FALSE, ...){
############################### INPUT CHECK ################################
if( !(is.null(username) || .is_non_empty_string(username)) ){
stop(
Expand All @@ -84,9 +83,9 @@ MgnifyClient <- function(
"'useCache' must be a boolean value specifying whether to use ",
"on-disk caching.", call. = FALSE)
}
if( !(is.null(cacheDir) || .is_non_empty_string(cacheDir)) ){
if( !.is_non_empty_string(cacheDir) ){
stop(
"'cacheDir' must be NULL or single character value specifying ",
"'cacheDir' must be single character value specifying ",
"the the directory for cache.", call. = FALSE)
}
if( !.is_a_bool(showWarnings) ){
Expand Down Expand Up @@ -127,24 +126,26 @@ MgnifyClient <- function(
stop("Failed to authenticate.", call. = FALSE)
}
}
# Assume we're not using it
cachepath <- NA_character_
# Get the directory where cache will be stored, if cache is used
if (is.null(cacheDir) ){
cachepath <- file.path(getwd(), ".MGnifyR_cache")
} else{
cachepath <- cacheDir
}
# Get the directory where cache will be stored.
# If user has specified the subdirectory, ensure that it works in any
# system by adding correct "/".
cacheDir <- as.list(strsplit(cacheDir, "[/\\\\]")[[1]])
cacheDir <- do.call(file.path, cacheDir)
# Add subdirectory. If user has specified for example working directory,
# the directory would be full of files. This is unintentional.
cacheDir <- file.path(cacheDir, ".MGnifyR_cache")
# Make it if needed - assume the user is sensible and the path will
# work...
dir.create(cachepath, showWarnings = FALSE)
if( useCache ){
dir.create(cacheDir, showWarnings = FALSE)
}
# Return the final object
obj <- new(
"MgnifyClient",
databaseUrl = url,
authTok = authtok,
useCache = useCache,
cacheDir = cachepath,
cacheDir = cacheDir,
showWarnings = showWarnings,
clearCache = clearCache,
verbose = verbose
Expand Down
2 changes: 0 additions & 2 deletions R/getResult.R
Original file line number Diff line number Diff line change
Expand Up @@ -496,8 +496,6 @@ setMethod("getResult", signature = c(x = "MgnifyClient"), function(
tse <- loadFromBiom(
biom_path, removeTaxaPrefixes = TRUE, only.taxa.col = TRUE,
rankFromPrefix = TRUE, remove.artifacts = TRUE)
# Remove unnecessary column from taxonomy data
rowData(tse)[["taxonomy_unparsed"]] <- NULL
# If the file was not in store already but fetched from database, and cache
# storing is disabled
if( fetched_from_url && !use.cache ){
Expand Down
12 changes: 5 additions & 7 deletions man/MgnifyClient.Rd

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

2 changes: 1 addition & 1 deletion tests/testthat/test-MgnifyClient.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ test_that("MgnifyClient", {
showWarnings = FALSE,
url = "test"
)
expect_equal(cacheDir(mg), "test")
expect_equal(cacheDir(mg), "test/.MGnifyR_cache")
expect_equal(showWarnings(mg), FALSE)
expect_equal(databaseUrl(mg), "test")
mg <- MgnifyClient(
Expand Down

0 comments on commit b216b06

Please sign in to comment.