Skip to content

Commit

Permalink
clear runtime cache each time a new instance is mounted
Browse files Browse the repository at this point in the history
  • Loading branch information
JsLth committed Sep 20, 2024
1 parent 6100221 commit a71cdab
Show file tree
Hide file tree
Showing 5 changed files with 88 additions and 6 deletions.
5 changes: 5 additions & 0 deletions R/local.R
Original file line number Diff line number Diff line change
Expand Up @@ -323,6 +323,11 @@ ORSLocal <- R6Class(
.prompts = TRUE,
.alive = TRUE,
.mount = function() {
if (!self$is_mounted()) {
# if a new instance is mounted, clear runtime cache
clear_runtime_cache()
}

# no idea why this is necessary but when just using envir = rors_cache
# $.mount() uses a different environment than defined globally
rors_cache <- get("rors_cache", envir = asNamespace("rors"))
Expand Down
7 changes: 4 additions & 3 deletions R/sample.R
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,7 @@
#' needs to be enabled on other servers. \code{ors_guess} can make a lot of
#' requests and might not be feasible in many situations.
#'
#' @inheritSection get_instance Caching
#'
#' @export
#'
Expand Down Expand Up @@ -85,7 +86,7 @@ ors_sample <- function(size,
get_extract_boundaries <- function(instance = NULL,
force = FALSE,
verbose = TRUE) {
recover_from_cache("extract_boundaries", force = force)
recover_from_cache("poly", force = force)
instance <- instance %||% get_instance()

if (ors_is_local(instance)) {
Expand Down Expand Up @@ -119,7 +120,7 @@ get_extract_boundaries <- function(instance = NULL,
poly <- proc$get_result()
} else {
tip <- paste(
"{.code get_extract_boundaries} is not usable for unkown remote",
"{.fn get_extract_boundaries} is not usable for unkown remote",
"servers as the extract boundaries cannot easily be determined.",
"Consider using {.fn ors_guess}."
)
Expand All @@ -129,7 +130,7 @@ get_extract_boundaries <- function(instance = NULL,
)
}

assign("extract_boundaries", poly, envir = rors_cache)
store_in_cache(poly)
poly
}

Expand Down
42 changes: 39 additions & 3 deletions R/utils-ors.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,29 @@ rors_cache <- new.env(parent = emptyenv())
recover_from_cache <- function(obj, force = FALSE) {
obj <- get0(obj, envir = rors_cache)
if (!is.null(obj) && !force) {
obj <- obj[[1]]
return_from_parent(obj, .envir = parent.frame())
}
}


store_in_cache <- function(obj) {
name <- deparse(substitute(obj))
obj <- list(obj)
class(obj) <- "rors_runtime_cache"
assign(name, obj, envir = rors_cache)
}


clear_runtime_cache <- function() {
is_runtime <- eapply(rors_cache, function(x) {
inherits(x, "rors_runtime_cache")
})
cached <- names(is_runtime)[unlist(is_runtime)]
rm(list = cached, envir = rors_cache)
}


#' Utility functions
#'
#' Utility functions to aid the setup of local instances.
Expand Down Expand Up @@ -51,6 +69,24 @@ recover_from_cache <- function(obj, force = FALSE) {
#' @seealso \code{\link{ors_instance}}
#' @export
#'
#' @section Caching:
#'
#' The following functions make use of a "runtime" caching system:
#' \code{ors_ready()}, \code{ors_status()}, \code{get_profiles()},
#' \code{get_extract_boundaries()}, \code{ors_sample()}. This means that,
#' if \code{force = FALSE}, previously generated output is re-used instead
#' of sending new requests. This can be particularly useful in automated
#' workflows like loops where speed is important. When run directly, caching
#' should not be necessary, which is why \code{force = FALSE} is the default
#' of most of these functions (except \code{get_extract_boundaries()} because
#' it deals with potentially much larger amounts of data).
#'
#' "Runtime" in this context refers to the runtime of an ORS instance, i.e.
#' the time after it is started. Cached results should only be valid for a
#' specific runtime and discarded afterwards. After starting or stopping
#' an instance or when mounting a new instance, the runtime cache is cleared
#' so that fresh requests must be made.
#'
#' @examples
#' # initialize an ORS instance
#' ors <- ors_instance(dir = tempdir(), dry = TRUE)
Expand Down Expand Up @@ -147,7 +183,7 @@ ors_status <- function(url = NULL, force = TRUE) {
)
}
class(status) <- "ors_status"
assign("status", status, envir = rors_cache)
store_in_cache(status)
status
}

Expand All @@ -171,7 +207,7 @@ get_profiles <- function(url = NULL, force = TRUE) {
ors_ready <- function(url = NULL, force = TRUE, error = FALSE) {
ready <- get0("ready", envir = rors_cache)
if (isTRUE(ready)) {
t <- recover_from_cache("ready", force = force)
recover_from_cache("ready", force = force)
}

url <- url %||% get_ors_url()
Expand Down Expand Up @@ -204,7 +240,7 @@ ors_ready <- function(url = NULL, force = TRUE, error = FALSE) {
)
}

assign("ready", ready, envir = rors_cache)
store_in_cache(ready)
ready
}

Expand Down
20 changes: 20 additions & 0 deletions man/get_instance.Rd

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

20 changes: 20 additions & 0 deletions man/ors_sample.Rd

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

0 comments on commit a71cdab

Please sign in to comment.