Skip to content

Commit

Permalink
Expand testing of separate running
Browse files Browse the repository at this point in the history
  • Loading branch information
richfitz committed Sep 21, 2023
1 parent 2d74ed6 commit 12f0745
Show file tree
Hide file tree
Showing 4 changed files with 69 additions and 6 deletions.
9 changes: 6 additions & 3 deletions R/context.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ orderly_context <- function(envir) {
if (is_active) {
path <- p$path
root <- p$root$path
root_src <- p$orderly2$root
config <- p$orderly2$config
envir <- p$orderly2$envir
src <- p$orderly2$src
Expand All @@ -13,7 +14,8 @@ orderly_context <- function(envir) {
search_options <- p$orderly2$search_options
} else {
path <- getwd()
root <- detect_orderly_interactive_path(path)
root_src <- detect_orderly_interactive_path(path)
root <- root_src # for now at least
config <- orderly_config_read(root)
src <- path
parameters <- current_orderly_parameters(src, envir)
Expand All @@ -22,8 +24,9 @@ orderly_context <- function(envir) {
search_options <- .interactive$search_options
}
list(is_active = is_active, path = path, config = config, envir = envir,
root = root, src = src, name = name, id = id, parameters = parameters,
search_options = search_options, packet = p)
root = root, root_src = root_src, src = src, name = name,
id = id, parameters = parameters, search_options = search_options,
packet = p)
}


Expand Down
2 changes: 1 addition & 1 deletion R/metadata.R
Original file line number Diff line number Diff line change
Expand Up @@ -321,7 +321,7 @@ orderly_shared_resource <- function(...) {
files <- validate_shared_resource(list(...), environment())
ctx <- orderly_context(rlang::caller_env())

files <- copy_shared_resource(ctx$root, ctx$path, ctx$config, files)
files <- copy_shared_resource(ctx$root_src, ctx$path, ctx$config, files)
if (ctx$is_active) {
outpack_packet_file_mark(ctx$packet, files$here, "immutable")
ctx$packet$orderly2$shared_resources <-
Expand Down
4 changes: 2 additions & 2 deletions R/run.R
Original file line number Diff line number Diff line change
Expand Up @@ -203,8 +203,8 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,
id = id, root = root)
outpack_packet_file_mark(p, "orderly.R", "immutable")
p$orderly2 <- list(config = root$config$orderly, envir = envir, src = src,
strict = dat$strict, inputs_info = inputs_info,
search_options = search_options)
root = root_src, strict = dat$strict,
inputs_info = inputs_info, search_options = search_options)
current[[path]] <- p
on.exit(current[[path]] <- NULL, add = TRUE, after = TRUE)
if (!is.null(parameters)) {
Expand Down
60 changes: 60 additions & 0 deletions tests/testthat/test-run-separate.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,3 +9,63 @@ test_that("can run simple case in separate directory", {
expect_true(file.exists(file.path(info$outpack, "archive")))
expect_true(file.exists(file.path(info$outpack, "archive", "explicit", id)))
})


test_that("can run shared resources case in separate directory", {
## This is worth a separate check as it's important that the shared
## resources are relative to the *source* tree and not the outpack
## root.
info <- test_prepare_orderly_example_separate("shared")
envir <- new.env()
id <- orderly_run_quietly("shared", envir = envir,
root = info$outpack, root_src = info$src)
expect_setequal(
dir(file.path(info$outpack, "archive", "shared", id)),
c("shared_data.csv", "mygraph.png", "orderly.R"))
})


test_that("can use dependencies in separate directory", {
## Ensures that we hit the outpack root for pulling deps in
info <- test_prepare_orderly_example_separate(c("data", "depends"))
envir1 <- new.env()
id1 <- orderly_run_quietly("data", envir = envir1,
root = info$outpack, root_src = info$src)
envir2 <- new.env()
id2 <- orderly_run_quietly("depends", envir = envir2,
root = info$outpack, root_src = info$src)

path1 <- file.path(info$outpack, "archive", "data", id1)
path2 <- file.path(info$outpack, "archive", "depends", id2)

expect_true(file.exists(file.path(path2, "input.rds")))
expect_equal(
unname(tools::md5sum(file.path(path2, "input.rds"))),
unname(tools::md5sum(file.path(path1, "data.rds"))))
})


test_that("can get git information in separate directory", {
info <- test_prepare_orderly_example_separate("explicit")
info$git <- helper_add_git(info$src)
id <- orderly_run_quietly("explicit", envir = new.env(),
root = info$outpack, root_src = info$src)
meta <- orderly_metadata(id, root = info$outpack)
expect_mapequal(meta$git, info$git[c("sha", "branch", "url")])
})


test_that("can't run interactively in separate directory", {
## Picking on depends here because it really requires the outpack
## root
info <- test_prepare_orderly_example_separate(c("data", "depends"))
envir1 <- new.env()
id1 <- orderly_run_quietly("data", envir = envir1,
root = info$outpack, root_src = info$src)
envir2 <- new.env()
path_src <- file.path(info$src, "src", "depends")
expect_error(
withr::with_dir(path_src,
sys.source("orderly.R", envir2)),
"orderly directory '.+' not initialised")
})

0 comments on commit 12f0745

Please sign in to comment.