From 7920c563ba5ce9c24534119cad062a57e552c655 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 14 Sep 2023 11:20:41 +0200 Subject: [PATCH 1/8] Allow for the two root types to be referenced separately --- R/cleanup.R | 12 ++++----- R/context.R | 6 ++--- R/gitignore.R | 36 ++++++++++++++----------- R/interactive.R | 3 +-- R/location.R | 2 +- R/orderly.R | 7 +++-- R/root.R | 28 +++++++++++++++++++- R/run.R | 21 ++++++++------- tests/testthat/test-gitignore.R | 10 +++---- tests/testthat/test-interactive.R | 3 +-- tests/testthat/test-root.R | 2 +- tests/testthat/test-run.R | 44 +++++++++++++++---------------- 12 files changed, 100 insertions(+), 74 deletions(-) diff --git a/R/cleanup.R b/R/cleanup.R index cd91dfe4..5750a335 100644 --- a/R/cleanup.R +++ b/R/cleanup.R @@ -104,18 +104,16 @@ orderly_cleanup_status <- function(name = NULL, root = NULL, locate = TRUE) { if (is.null(name) && is.null(root)) { path <- getwd() - root <- detect_orderly_interactive_path(path)$path + root_path <- detect_orderly_interactive_path(path) name <- basename(path) } else { - root <- root_open(root, locate = locate, require_orderly = TRUE, - call = environment()) + root_path <- orderly_src_root(root, locate, call = environment()) if (is.null(name)) { ## This situation would be very odd, just disallow it cli::cli_abort("If 'root' is given explicitly, 'name' is required") } - name <- validate_orderly_directory(name, root, environment()) - path <- file.path(root$path, "src", name) - root <- root$path + name <- validate_orderly_directory(name, root_path, environment()) + path <- file.path(root_path, "src", name) } info <- orderly_read(path) @@ -164,7 +162,7 @@ orderly_cleanup_status <- function(name = NULL, root = NULL, locate = TRUE) { unknown <- files[!is_source & !to_delete] structure(list(name = name, - root = root, + root = root_path, path = path, role = role, status = status, diff --git a/R/context.R b/R/context.R index 6e117a86..9e47ec91 100644 --- a/R/context.R +++ b/R/context.R @@ -13,10 +13,8 @@ orderly_context <- function(envir) { search_options <- p$orderly2$search_options } else { path <- getwd() - root <- detect_orderly_interactive_path(path)$path - config <- root_open(root, - locate = FALSE, - require_orderly = TRUE)$config$orderly + root <- detect_orderly_interactive_path(path) + config <- orderly_config_read(root) src <- path parameters <- current_orderly_parameters(src, envir) name <- basename(path) diff --git a/R/gitignore.R b/R/gitignore.R index 657c8ac5..56099194 100644 --- a/R/gitignore.R +++ b/R/gitignore.R @@ -34,41 +34,45 @@ ##' @return Nothing, called for its side effects ##' @export orderly_gitignore_update <- function(name, root = NULL, locate = TRUE) { - root <- root_open(root, locate, require_orderly = TRUE, call = environment()) - do_orderly_gitignore_update(name, root, environment()) + root_path <- orderly_src_root(root, locate, call = environment()) + do_orderly_gitignore_update(name, root_path, environment()) } ## Separate inned function that avoids opening the root, we need this ## to break a circular dependency as we sometimes call this function ## while openning the root. -do_orderly_gitignore_update <- function(name, root, call) { +do_orderly_gitignore_update <- function(name, root_path, call) { assert_scalar_character(name) if (name == "(root)") { path <- ".gitignore" - value <- gitignore_content_root(root) + value <- gitignore_content_root(root_path) } else { - name <- validate_orderly_directory(name, root, call) + name <- validate_orderly_directory(name, root_path, call) path <- file.path("src", name, ".gitignore") - value <- gitignore_content_src(name, root) + value <- gitignore_content_src(name, root_path) } - if (gitignore_update_file(root$path, path, value)) { + if (gitignore_update_file(root_path, path, value)) { cli::cli_alert_success("Wrote '{path}'") } invisible(TRUE) } -gitignore_content_root <- function(root) { +gitignore_content_root <- function(root_path) { + path_archive <- NULL + if (file.exists(file.path(root_path, ".outpack", "config.json"))) { + path_archive <- config_read(root_path)$core$path_archive + } c(".outpack", "orderly_envir.yml", "draft", - root$config$core$path_archive) + path_archive) } -gitignore_content_src <- function(name, root) { - dat <- orderly_read_r(file.path(root$path, "src", name, "orderly.R")) +gitignore_content_src <- function(name, root_path) { + dat <- orderly_read_r(file.path(root_path, "src", name, "orderly.R")) ignore_deps <- unlist(lapply(dat$dependency, function(x) names(x$files))) ignore_artefacts <- unlist(lapply(dat$artefacts, "[[", "files")) @@ -89,7 +93,7 @@ gitignore_markers <- c( "# ---^^^--- added by orderly ---^^^----------------") -gitignore_update_contents <- function(content_old, value, path, root) { +gitignore_update_contents <- function(content_old, value, path, root_path) { if (!any(gitignore_markers %in% content_old)) { if (length(content_old) > 0) { content_old <- c(content_old, "") @@ -106,7 +110,7 @@ gitignore_update_contents <- function(content_old, value, path, root) { if (err) { cli::cli_abort(c( "Can't edit '{path}', markers are corrupted", - i = "(within orderly root '{root}')", + i = "(within orderly root '{root_path}')", i = "Please see ?orderly_gitignore_update for more details")) } @@ -117,11 +121,11 @@ gitignore_update_contents <- function(content_old, value, path, root) { } -gitignore_update_file <- function(root, path, value) { - path_full <- file.path(root, path) +gitignore_update_file <- function(root_path, path, value) { + path_full <- file.path(root_path, path) gitignore_exists <- file.exists(path_full) content_old <- if (gitignore_exists) readLines(path_full) else character() - content_new <- gitignore_update_contents(content_old, value, path, root) + content_new <- gitignore_update_contents(content_old, value, path, root_path) if (identical(content_old, content_new)) { return(FALSE) } diff --git a/R/interactive.R b/R/interactive.R index a92854d2..d8dedf30 100644 --- a/R/interactive.R +++ b/R/interactive.R @@ -12,8 +12,7 @@ detect_orderly_interactive_path <- function(path = getwd()) { if (!is_plausible) { stop(sprintf("Failed to detect orderly path at '%s'", path)) } - root_path <- as.character(fs::path_norm(file.path(path, "../.."))) - root_open(root_path, locate = FALSE, require_orderly = TRUE) + as.character(fs::path_norm(file.path(path, "../.."))) } diff --git a/R/location.R b/R/location.R index f9f16abc..098386a8 100644 --- a/R/location.R +++ b/R/location.R @@ -358,7 +358,7 @@ orderly_location_pull_packet <- function(..., options = NULL, recursive = NULL, ##' @export orderly_location_push <- function(packet_id, location, root = NULL, locate = TRUE) { - root <- root_open(root, locate = locate, require_orderly = TRUE, + root <- root_open(root, locate = locate, require_orderly = FALSE, call = environment()) location_name <- location_resolve_valid(location, root, include_local = FALSE, diff --git a/R/orderly.R b/R/orderly.R index 5659d460..6ede1d3d 100644 --- a/R/orderly.R +++ b/R/orderly.R @@ -16,11 +16,10 @@ ##' path <- orderly2::orderly_example("default") ##' orderly2::orderly_list_src(root = path) orderly_list_src <- function(root = NULL, locate = TRUE) { - root <- root_open(root, locate = locate, require_orderly = TRUE, - call = environment()) - if (!file.exists(file.path(root$path, "src"))) { + root_path <- orderly_src_root(root, locate) + if (!file.exists(file.path(root_path, "src"))) { return(character()) } - pos <- fs::dir_ls(file.path(root$path, "src"), type = "directory") + pos <- fs::dir_ls(file.path(root_path, "src"), type = "directory") basename(pos)[file_exists(file.path(pos, "orderly.R"))] } diff --git a/R/root.R b/R/root.R index 638ec4a6..7397256f 100644 --- a/R/root.R +++ b/R/root.R @@ -206,6 +206,32 @@ root_open <- function(path, locate, require_orderly = FALSE, call = NULL) { } +orderly_src_root <- function(path, locate, call = NULL) { + if (inherits(path, "outpack_root")) { + path <- path$path + locate <- FALSE + } + if (is.null(path)) { + path <- getwd() + } + assert_scalar_character(path) + assert_is_directory(path) + + limit <- if (locate) "/" else path + path_root <- find_file_descend("orderly_config.yml", path, limit) + if (is.null(path_root)) { + cli::cli_abort( + c(sprintf( + "Did not find existing orderly source root in '%s'", path), + i = "Expected to find file 'orderly_config.yml'", + i = if (locate) "Looked in parents of this path without success"), + call = call) + } + + path_root +} + + ## This is pretty unpleasant, but does the trick. root_validate_same_configuration <- function(args, config, root, call) { argmap <- list( @@ -275,7 +301,7 @@ root_check_git <- function(root, call) { } } - do_orderly_gitignore_update("(root)", root) + do_orderly_gitignore_update("(root)", root$path) fs::dir_create(dirname(path_ok)) fs::file_create(path_ok) diff --git a/R/run.R b/R/run.R index 9eaf41f2..604e7690 100644 --- a/R/run.R +++ b/R/run.R @@ -130,19 +130,22 @@ ##' orderly2::orderly_metadata_extract(name = "data", root = path) orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE, search_options = NULL, root = NULL, locate = TRUE) { - root <- root_open(root, locate, require_orderly = TRUE, call = environment()) - name <- validate_orderly_directory(name, root, environment()) + root <- root_open(root, locate, require_orderly = TRUE, + call = environment()) + root_src <- root$path + + name <- validate_orderly_directory(name, root_src, environment()) envir <- envir %||% .GlobalEnv assert_is(envir, "environment") - src <- file.path(root$path, "src", name) + src <- file.path(root_src, "src", name) dat <- orderly_read(src) parameters <- check_parameters(parameters, dat$parameters, environment()) orderly_validate(dat, src) id <- outpack_id() - path <- file.path(root$path, "draft", name, id) + path <- file.path(root_src, "draft", name, id) fs::dir_create(path) ## Slightly peculiar formulation here; we're going to use 'path' as @@ -487,13 +490,13 @@ orderly_packet_add_metadata <- function(p) { } -validate_orderly_directory <- function(name, root, call) { +validate_orderly_directory <- function(name, root_path, call) { assert_scalar_character(name) re <- "^(./)*(src/)?(.+?)/?$" name <- sub(re, "\\3", name) - if (!file_exists(file.path(root$path, "src", name, "orderly.R"))) { - src <- file.path(root$path, "src", name) + if (!file_exists(file.path(root_path, "src", name, "orderly.R"))) { + src <- file.path(root_path, "src", name) err <- sprintf("Did not find orderly report '%s'", name) if (!file_exists(src)) { detail <- sprintf("The path 'src/%s' does not exist", name) @@ -507,14 +510,14 @@ validate_orderly_directory <- function(name, root, call) { name) } err <- c(err, x = detail) - near <- near_match(name, orderly_list_src(root, FALSE)) + near <- near_match(name, orderly_list_src(root_path, FALSE)) if (length(near) > 0) { hint <- sprintf("Did you mean %s", paste(squote(near), collapse = ", ")) err <- c(err, i = hint) } err <- c(err, i = sprintf("Looked relative to orderly root at '%s'", - root$path)) + root_path)) cli::cli_abort(err, call = call) } diff --git a/tests/testthat/test-gitignore.R b/tests/testthat/test-gitignore.R index 4a6e7fb9..97c36d3d 100644 --- a/tests/testthat/test-gitignore.R +++ b/tests/testthat/test-gitignore.R @@ -130,7 +130,7 @@ test_that("can update file with existing contents", { test_that("can add a basic root gitignore", { path <- test_prepare_orderly_example("data") ignore <- c(".outpack", "orderly_envir.yml", "draft", "archive") - expect_equal(gitignore_content_root(root_open(path, FALSE, FALSE)), ignore) + expect_equal(gitignore_content_root(path), ignore) expect_message( expect_true(orderly_gitignore_update("(root)", path)), "Wrote '.gitignore'") @@ -143,7 +143,7 @@ test_that("can add a basic root gitignore", { test_that("can add a source .gitignore", { path <- test_prepare_orderly_example("data") ignore <- c("data.rds") - expect_equal(gitignore_content_src("data", root_open(path, FALSE, FALSE)), + expect_equal(gitignore_content_src("data", path), ignore) expect_message( expect_true(orderly_gitignore_update("data", path)), @@ -157,7 +157,7 @@ test_that("can add a source .gitignore", { test_that("can compute ignore for dependencies", { path <- test_prepare_orderly_example("depends") expect_equal( - gitignore_content_src("depends", root_open(path, FALSE, FALSE)), + gitignore_content_src("depends", path), c("input.rds", "graph.png")) }) @@ -165,7 +165,7 @@ test_that("can compute ignore for dependencies", { test_that("can compute ignore for dependencies", { path <- test_prepare_orderly_example("shared") expect_setequal( - gitignore_content_src("shared", root_open(path, FALSE, FALSE)), + gitignore_content_src("shared", path), c("mygraph.png", "shared_data.csv")) }) @@ -173,6 +173,6 @@ test_that("can compute ignore for dependencies", { test_that("don't ignore resources that are artefacts", { path <- test_prepare_orderly_example("reexport") expect_equal( - gitignore_content_src("reexport", root_open(path, FALSE, FALSE)), + gitignore_content_src("reexport", path), "mygraph.png") }) diff --git a/tests/testthat/test-interactive.R b/tests/testthat/test-interactive.R index 44f92fdb..fc5171a1 100644 --- a/tests/testthat/test-interactive.R +++ b/tests/testthat/test-interactive.R @@ -10,6 +10,5 @@ test_that("can detect orderly directory", { detect_orderly_interactive_path(file.path(path, "src")), "Failed to detect orderly path at") root <- detect_orderly_interactive_path(file.path(path, "src", "explicit")) - expect_s3_class(root, "outpack_root") - expect_type(root$config$orderly, "list") + expect_equal(path, root) }) diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index 60b053fd..27530c87 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -84,7 +84,7 @@ test_that("can add gitignore if git setup is ok, but not present", { test_that("can error with instructions if files are added to git", { root <- create_temporary_root() info <- helper_add_git(root$path) - id <- create_random_packet(root) + id <- create_random_packet(root$path) ## Need to do some work here to make this fail now: fs::file_delete(file.path(root$path, ".gitignore")) diff --git a/tests/testthat/test-run.R b/tests/testthat/test-run.R index 0557b0ae..edcf21b1 100644 --- a/tests/testthat/test-run.R +++ b/tests/testthat/test-run.R @@ -869,7 +869,7 @@ test_that("validation of orderly directories", { hint_root <- sprintf("Looked relative to orderly root at '%s'", root$path) err <- expect_error( - validate_orderly_directory("foo", root), + validate_orderly_directory("foo", path), "Did not find orderly report 'foo'") expect_equal(err$body, c(x = "The path 'src/foo' does not exist", @@ -877,7 +877,7 @@ test_that("validation of orderly directories", { file.create(file.path(path, "src", "foo")) err <- expect_error( - validate_orderly_directory("foo", root), + validate_orderly_directory("foo", path), "Did not find orderly report 'foo'") expect_equal(err$body, c(x = "The path 'src/foo' exists but is not a directory", @@ -885,7 +885,7 @@ test_that("validation of orderly directories", { fs::dir_create(file.path(path, "src", "bar")) err <- expect_error( - validate_orderly_directory("bar", root), + validate_orderly_directory("bar", path), "Did not find orderly report 'bar'") expect_equal( err$body, @@ -895,7 +895,7 @@ test_that("validation of orderly directories", { hint_close <- sprintf("Did you mean %s", paste(squote(nms[1:5]), collapse = ", ")) err <- expect_error( - validate_orderly_directory("example_z", root), + validate_orderly_directory("example_z", path), "Did not find orderly report 'example_z'") expect_equal(err$body, c(x = "The path 'src/example_z' does not exist", @@ -904,7 +904,7 @@ test_that("validation of orderly directories", { file.create(file.path(path, "src", "example_z")) err <- expect_error( - validate_orderly_directory("example_z", root), + validate_orderly_directory("example_z", path), "Did not find orderly report 'example_z'") expect_equal(err$body, c(x = "The path 'src/example_z' exists but is not a directory", @@ -913,7 +913,7 @@ test_that("validation of orderly directories", { fs::dir_create(file.path(path, "src", "example_x")) err <- expect_error( - validate_orderly_directory("example_x", root), + validate_orderly_directory("example_x", path), "Did not find orderly report 'example_x'") expect_equal( err$body, @@ -930,42 +930,42 @@ test_that("strip extraneous path components from orderly path", { fs::dir_create(file.path(path, "src", "example_a")) file.create(file.path(path, "src", "example_a", "orderly.R")) - expect_equal(validate_orderly_directory("example_a", root), + expect_equal(validate_orderly_directory("example_a", path), "example_a") - expect_equal(validate_orderly_directory("src/example_a", root), + expect_equal(validate_orderly_directory("src/example_a", path), "example_a") - expect_equal(validate_orderly_directory("./src/example_a", root), + expect_equal(validate_orderly_directory("./src/example_a", path), "example_a") - expect_equal(validate_orderly_directory("./example_a", root), + expect_equal(validate_orderly_directory("./example_a", path), "example_a") - expect_equal(validate_orderly_directory("example_a/", root), + expect_equal(validate_orderly_directory("example_a/", path), "example_a") - expect_equal(validate_orderly_directory("src/example_a/", root), + expect_equal(validate_orderly_directory("src/example_a/", path), "example_a") - expect_equal(validate_orderly_directory("./src/example_a/", root), + expect_equal(validate_orderly_directory("./src/example_a/", path), "example_a") - expect_equal(validate_orderly_directory("./example_a/", root), + expect_equal(validate_orderly_directory("./example_a/", path), "example_a") ## Pathalogical case: fs::dir_create(file.path(path, "src", "src")) file.create(file.path(path, "src", "src", "orderly.R")) - expect_equal(validate_orderly_directory("src", root), + expect_equal(validate_orderly_directory("src", path), "src") - expect_equal(validate_orderly_directory("src/src", root), + expect_equal(validate_orderly_directory("src/src", path), "src") - expect_equal(validate_orderly_directory("./src/src", root), + expect_equal(validate_orderly_directory("./src/src", path), "src") - expect_equal(validate_orderly_directory("./src", root), + expect_equal(validate_orderly_directory("./src", path), "src") - expect_equal(validate_orderly_directory("src/", root), + expect_equal(validate_orderly_directory("src/", path), "src") - expect_equal(validate_orderly_directory("src/src/", root), + expect_equal(validate_orderly_directory("src/src/", path), "src") - expect_equal(validate_orderly_directory("./src/src/", root), + expect_equal(validate_orderly_directory("./src/src/", path), "src") - expect_equal(validate_orderly_directory("./src/", root), + expect_equal(validate_orderly_directory("./src/", path), "src") }) From 2d74ed67af73e54d78251cdaf471ce41d14b5b70 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 21 Sep 2023 17:49:25 +0100 Subject: [PATCH 2/8] Start running separately --- R/run.R | 44 +++++++++++++++++++++++++++--- man/orderly_run.Rd | 35 +++++++++++++++++++++++- tests/testthat/helper-orderly.R | 42 ++++++++++++++++++++++------ tests/testthat/test-run-separate.R | 11 ++++++++ 4 files changed, 118 insertions(+), 14 deletions(-) create mode 100644 tests/testthat/test-run-separate.R diff --git a/R/run.R b/R/run.R index 604e7690..7acca951 100644 --- a/R/run.R +++ b/R/run.R @@ -81,6 +81,29 @@ ##' functionality was never available in orderly version 1, though ##' we had intended to support it. ##' +##' @section Running with a source tree separate from outpack root: +##' +##' Sometimes it is useful to run things from a different place on +##' disk to your outpack root. We know of two cases where this has +##' come up: +##' +##' * when running reports within a runner on a server, we make a +##' clean clone of the source tree at a particular git reference +##' into a new temporary directory and then run the report there, +##' but have it insert into an orderly repo at a fixed and +##' non-temporary location. +##' * we have a user for whom it is more convenient torun their report +##' on a hard drive but store the archive and metadata on a (larger) +##' shared drive. +##' +##' In the first instance, we have a source path at `` which +##' contains the file `orderly_config.yml` and the directory `src/` +##' with our source reports, and a separate path `` which +##' contains the directory `.outpack/` with all the metadata - it +##' may also have an unpacked archive, and a `.git/` directory +##' depending on the configuration. (Later this will make more sense +##' once we support a "bare" outpack layout.) +##' ##' @title Run a report ##' ##' @param name Name of the report to run. Any leading `./` `src/` or @@ -113,6 +136,12 @@ ##' then orderly looks in the working directory and up through its ##' parents until it finds an `.outpack` directory ##' +##' @param root_src Separately, the root of the orderly source tree, +##' if separate from the outpack root (given as `root`). This is +##' intended for running reports in situations where the source tree +##' is kept in a different place to the outpack root; see Details +##' for more information. +##' ##' @return The id of the created report (a string) ##' ##' @export @@ -129,10 +158,17 @@ ##' # and we can query the metadata: ##' orderly2::orderly_metadata_extract(name = "data", root = path) orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE, - search_options = NULL, root = NULL, locate = TRUE) { - root <- root_open(root, locate, require_orderly = TRUE, - call = environment()) - root_src <- root$path + search_options = NULL, root = NULL, locate = TRUE, + root_src = NULL) { + if (is.null(root_src)) { + root <- root_open(root, locate, require_orderly = TRUE, + call = environment()) + root_src <- root$path + } else { + root <- root_open(root, locate, require_orderly = FALSE, + call = environment()) + root_src <- orderly_src_root(root_src, locate, call = environment()) + } name <- validate_orderly_directory(name, root_src, environment()) diff --git a/man/orderly_run.Rd b/man/orderly_run.Rd index 360bf5c0..c5a40319 100644 --- a/man/orderly_run.Rd +++ b/man/orderly_run.Rd @@ -11,7 +11,8 @@ orderly_run( echo = TRUE, search_options = NULL, root = NULL, - locate = TRUE + locate = TRUE, + root_src = NULL ) } \arguments{ @@ -44,6 +45,12 @@ directory is configured for orderly, and not just outpack (see searched for. If \code{TRUE} and \code{config} is not given, then orderly looks in the working directory and up through its parents until it finds an \code{.outpack} directory} + +\item{root_src}{Separately, the root of the orderly source tree, +if separate from the outpack root (given as \code{root}). This is +intended for running reports in situations where the source tree +is kept in a different place to the outpack root; see Details +for more information.} } \value{ The id of the created report (a string) @@ -137,6 +144,32 @@ functionality was never available in orderly version 1, though we had intended to support it. } +\section{Running with a source tree separate from outpack root}{ + + +Sometimes it is useful to run things from a different place on +disk to your outpack root. We know of two cases where this has +come up: +\itemize{ +\item when running reports within a runner on a server, we make a +clean clone of the source tree at a particular git reference +into a new temporary directory and then run the report there, +but have it insert into an orderly repo at a fixed and +non-temporary location. +\item we have a user for whom it is more convenient torun their report +on a hard drive but store the archive and metadata on a (larger) +shared drive. +} + +In the first instance, we have a source path at \verb{} which +contains the file \code{orderly_config.yml} and the directory \verb{src/} +with our source reports, and a separate path \verb{} which +contains the directory \verb{.outpack/} with all the metadata - it +may also have an unpacked archive, and a \verb{.git/} directory +depending on the configuration. (Later this will make more sense +once we support a "bare" outpack layout.) +} + \examples{ # Create a simple example: path <- orderly2::orderly_example("default") diff --git a/tests/testthat/helper-orderly.R b/tests/testthat/helper-orderly.R index 2cba992f..39a1d8be 100644 --- a/tests/testthat/helper-orderly.R +++ b/tests/testthat/helper-orderly.R @@ -6,17 +6,42 @@ options(outpack.schema_validate = test_prepare_orderly_example <- function(examples, ...) { tmp <- tempfile() withr::defer_parent(unlink(tmp, recursive = TRUE)) - suppressMessages(orderly_init(tmp)) - config <- readLines(file.path(tmp, "orderly_config.yml")) + suppressMessages(orderly_init(tmp, ...)) + copy_examples(examples, tmp) + tmp +} + + +test_prepare_orderly_example_separate <- function(examples, ...) { + tmp <- tempfile() + withr::defer_parent(unlink(tmp, recursive = TRUE)) + + path_outpack <- file.path(tmp, "outpack") + suppressMessages(orderly_init(path_outpack, ...)) + + path_src <- file.path(tmp, "src") + copy_examples(examples, path_src) + list(src = path_src, outpack = path_outpack) +} + + +copy_examples <- function(examples, path_src) { + if (file.exists(path_src)) { + config <- readLines(file.path(path_src, "orderly_config.yml")) + } else { + config <- empty_config_contents() + } + + fs::dir_create(path_src) if (any(c("shared", "shared-dir") %in% examples)) { - fs::dir_create(file.path(tmp, "shared")) + fs::dir_create(file.path(path_src, "shared")) if ("shared" %in% examples) { fs::file_copy(test_path("examples/explicit/data.csv"), - file.path(tmp, "shared")) + file.path(path_src, "shared")) } if ("shared-dir" %in% examples) { - fs::dir_create(file.path(tmp, "shared", "data")) + fs::dir_create(file.path(path_src, "shared", "data")) } } @@ -28,13 +53,12 @@ test_prepare_orderly_example <- function(examples, ...) { " distribution:", " normal") } + writeLines(config, file.path(path_src, "orderly_config.yml")) - writeLines(config, file.path(tmp, "orderly_config.yml")) - fs::dir_create(file.path(tmp, "src")) + fs::dir_create(file.path(path_src, "src")) for (i in examples) { - fs::dir_copy(test_path("examples", i), file.path(tmp, "src")) + fs::dir_copy(test_path("examples", i), file.path(path_src, "src")) } - tmp } diff --git a/tests/testthat/test-run-separate.R b/tests/testthat/test-run-separate.R new file mode 100644 index 00000000..3c32b20a --- /dev/null +++ b/tests/testthat/test-run-separate.R @@ -0,0 +1,11 @@ +test_that("can run simple case in separate directory", { + info <- test_prepare_orderly_example_separate("explicit") + id <- orderly_run_quietly("explicit", envir = new.env(), + root = info$outpack, root_src = info$src) + expect_type(id, "character") + expect_true(file.exists(file.path(info$src, "draft"))) + expect_false(file.exists(file.path(info$src, "archive"))) + expect_false(file.exists(file.path(info$outpack, "draft"))) + expect_true(file.exists(file.path(info$outpack, "archive"))) + expect_true(file.exists(file.path(info$outpack, "archive", "explicit", id))) +}) From 12f074568e958ea28c5f226a565b53e711d73988 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 21 Sep 2023 18:26:10 +0100 Subject: [PATCH 3/8] Expand testing of separate running --- R/context.R | 9 +++-- R/metadata.R | 2 +- R/run.R | 4 +- tests/testthat/test-run-separate.R | 60 ++++++++++++++++++++++++++++++ 4 files changed, 69 insertions(+), 6 deletions(-) diff --git a/R/context.R b/R/context.R index 9e47ec91..77d49eb2 100644 --- a/R/context.R +++ b/R/context.R @@ -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 @@ -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) @@ -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) } diff --git a/R/metadata.R b/R/metadata.R index 35cf447e..a4e4b307 100644 --- a/R/metadata.R +++ b/R/metadata.R @@ -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 <- diff --git a/R/run.R b/R/run.R index 7acca951..2e30d07a 100644 --- a/R/run.R +++ b/R/run.R @@ -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)) { diff --git a/tests/testthat/test-run-separate.R b/tests/testthat/test-run-separate.R index 3c32b20a..2177368a 100644 --- a/tests/testthat/test-run-separate.R +++ b/tests/testthat/test-run-separate.R @@ -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") +}) From 72a26b39fe726946830d5b85486aa290b6e32816 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Fri, 22 Sep 2023 10:21:19 +0100 Subject: [PATCH 4/8] Expand testing --- tests/testthat/helper-orderly.R | 1 + tests/testthat/test-root.R | 26 ++++++++++++++++++++++++++ 2 files changed, 27 insertions(+) diff --git a/tests/testthat/helper-orderly.R b/tests/testthat/helper-orderly.R index 39a1d8be..9bc4d1fc 100644 --- a/tests/testthat/helper-orderly.R +++ b/tests/testthat/helper-orderly.R @@ -18,6 +18,7 @@ test_prepare_orderly_example_separate <- function(examples, ...) { path_outpack <- file.path(tmp, "outpack") suppressMessages(orderly_init(path_outpack, ...)) + unlink(file.path(path_outpack, "orderly_config.yml")) path_src <- file.path(tmp, "src") copy_examples(examples, path_src) diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index 27530c87..f714c03e 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -117,3 +117,29 @@ test_that("can error with instructions if files are added to git", { expect_warning(id2 <- create_random_packet(root$path), NA)) # no warning expect_type(id2, "character") }) + + +test_that("can identify a plain source root", { + info <- test_prepare_orderly_example_separate("explicit") + expect_equal(orderly_src_root(info$src, FALSE), info$src) + expect_equal(orderly_src_root(file.path(info$src, "src", "explicit"), TRUE), + info$src) + expect_error( + orderly_src_root(file.path(info$src, "src", "explicit"), FALSE), + "Did not find existing orderly source root in") + + p <- file.path(info$outpack, "a", "b", "c") + fs::dir_create(p) + + err <- expect_error( + orderly_src_root(info$outpack, FALSE), + "Did not find existing orderly source root in") + expect_equal(err$body, c(i = "Expected to find file 'orderly_config.yml'")) + + err <- expect_error( + orderly_src_root(p, TRUE), + "Did not find existing orderly source root in") + expect_equal(err$body, + c(i = "Expected to find file 'orderly_config.yml'", + i = "Looked in parents of this path without success")) +}) From 871d0611f215b925e09dcb10232824922a519e6e Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Fri, 22 Sep 2023 10:49:24 +0100 Subject: [PATCH 5/8] Fix macos platform-specific failures --- tests/testthat/helper-orderly.R | 2 +- tests/testthat/test-run.R | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/testthat/helper-orderly.R b/tests/testthat/helper-orderly.R index 9bc4d1fc..52e9e57b 100644 --- a/tests/testthat/helper-orderly.R +++ b/tests/testthat/helper-orderly.R @@ -8,7 +8,7 @@ test_prepare_orderly_example <- function(examples, ...) { withr::defer_parent(unlink(tmp, recursive = TRUE)) suppressMessages(orderly_init(tmp, ...)) copy_examples(examples, tmp) - tmp + as.character(fs::path_norm(tmp)) } diff --git a/tests/testthat/test-run.R b/tests/testthat/test-run.R index edcf21b1..1fa8a83d 100644 --- a/tests/testthat/test-run.R +++ b/tests/testthat/test-run.R @@ -866,7 +866,7 @@ test_that("validation of orderly directories", { nms <- sprintf("example_%s", letters[1:8]) fs::dir_create(file.path(path, "src", nms)) file.create(file.path(path, "src", nms, "orderly.R")) - hint_root <- sprintf("Looked relative to orderly root at '%s'", root$path) + hint_root <- sprintf("Looked relative to orderly root at '%s'", path) err <- expect_error( validate_orderly_directory("foo", path), From a48d50e37f342be32dd6d3094f027fac3b86c73c Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Fri, 22 Sep 2023 11:05:57 +0100 Subject: [PATCH 6/8] Normalise more paths in tests --- tests/testthat/test-root.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index f714c03e..31b768ef 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -121,9 +121,9 @@ test_that("can error with instructions if files are added to git", { test_that("can identify a plain source root", { info <- test_prepare_orderly_example_separate("explicit") - expect_equal(orderly_src_root(info$src, FALSE), info$src) + expect_equal(orderly_src_root(info$src, FALSE), normalizePath(info$src)) expect_equal(orderly_src_root(file.path(info$src, "src", "explicit"), TRUE), - info$src) + normalizePath(info$src)) expect_error( orderly_src_root(file.path(info$src, "src", "explicit"), FALSE), "Did not find existing orderly source root in") From ea0d47a17b9b00e6ac99d7a0708b82ee7674330d Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Fri, 22 Sep 2023 15:57:27 +0100 Subject: [PATCH 7/8] Windows platform-specific path test fixes --- tests/testthat/test-cleanup.R | 3 ++- tests/testthat/test-root.R | 8 +++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/tests/testthat/test-cleanup.R b/tests/testthat/test-cleanup.R index 845969f6..b8a3c612 100644 --- a/tests/testthat/test-cleanup.R +++ b/tests/testthat/test-cleanup.R @@ -11,7 +11,8 @@ test_that("can cleanup explicit things quite well", { names(status), c("name", "root", "path", "role", "status", "delete", "unknown")) expect_equal(status$name, "explicit") - expect_equal(status$root, root_open(path, FALSE, FALSE)$path) + expect_equal(normalise_path(status$root), + normalise_path(root_open(path, FALSE, FALSE)$path)) expect_equal(normalise_path(status$path), normalise_path(file.path(status$root, "src", status$name))) paths <- c("data.csv", "mygraph.png", "orderly.R") diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index 31b768ef..7a8e1115 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -121,9 +121,11 @@ test_that("can error with instructions if files are added to git", { test_that("can identify a plain source root", { info <- test_prepare_orderly_example_separate("explicit") - expect_equal(orderly_src_root(info$src, FALSE), normalizePath(info$src)) - expect_equal(orderly_src_root(file.path(info$src, "src", "explicit"), TRUE), - normalizePath(info$src)) + expect_equal(normalise_path(orderly_src_root(info$src, FALSE)), + normalise_path(info$src)) + expect_equal( + orderly_src_root(file.path(info$src, "src", "explicit"), TRUE), + orderly_src_root(info$src, FALSE)) expect_error( orderly_src_root(file.path(info$src, "src", "explicit"), FALSE), "Did not find existing orderly source root in") From 0a82118c3994bbe69b68b4da7afbbc3b7ef95a9c Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Fri, 22 Sep 2023 16:52:31 +0100 Subject: [PATCH 8/8] Expand testing --- tests/testthat/test-root.R | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index 7a8e1115..9fb12579 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -145,3 +145,11 @@ test_that("can identify a plain source root", { c(i = "Expected to find file 'orderly_config.yml'", i = "Looked in parents of this path without success")) }) + + +test_that("can identify a plain source root from a full root", { + path <- test_prepare_orderly_example("explicit") + root <- root_open(path, FALSE) + expect_equal(orderly_src_root(root$path, FALSE), root$path) + expect_equal(orderly_src_root(root, FALSE), root$path) +})