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") })