From 18f4b7b266124154ffd38c01752dd4aa8464b3d2 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 17 Oct 2024 13:57:42 +0100 Subject: [PATCH] Just don't search almost ever --- R/context.R | 2 +- R/location.R | 2 +- R/location_path.R | 2 +- R/outpack_checksum.R | 2 +- R/outpack_packet.R | 2 +- R/query_index.R | 2 +- R/root.R | 20 +++++++------------- tests/testthat/helper-outpack.R | 2 +- tests/testthat/test-cleanup.R | 2 +- tests/testthat/test-init.R | 6 +++--- tests/testthat/test-location.R | 6 +++--- tests/testthat/test-outpack-root.R | 20 ++++++++++---------- tests/testthat/test-plugin.R | 2 +- tests/testthat/test-root.R | 19 +++++++++++-------- tests/testthat/test-run.R | 4 ++-- 15 files changed, 45 insertions(+), 48 deletions(-) diff --git a/R/context.R b/R/context.R index 255f637f..7ff98532 100644 --- a/R/context.R +++ b/R/context.R @@ -62,7 +62,7 @@ orderly_run_info <- function() { id <- ctx$packet$id %||% NA_character_ name <- ctx$name - root <- root_open(ctx$root, locate = FALSE, require_orderly = TRUE) + root <- root_open(ctx$root, require_orderly = TRUE) deps <- ctx$packet$depends deps_n <- vnapply(deps, function(x) nrow(x$files)) diff --git a/R/location.R b/R/location.R index 6819a642..ddbc3c42 100644 --- a/R/location.R +++ b/R/location.R @@ -105,7 +105,7 @@ orderly_location_add <- function(name, type, args, root = NULL) { ## providing the user with anything actionable yet. assert_scalar_character(loc$args[[1]]$path, name = "args$path", call = environment()) - root_open(loc$args[[1]]$path, locate = FALSE, require_orderly = FALSE) + root_open(loc$args[[1]]$path, require_orderly = FALSE) } else if (type == "http") { assert_scalar_character(loc$args[[1]]$url, name = "args$url", call = environment()) diff --git a/R/location_path.R b/R/location_path.R index d548ebdf..3cb7ea30 100644 --- a/R/location_path.R +++ b/R/location_path.R @@ -7,7 +7,7 @@ orderly_location_path <- R6::R6Class( public = list( initialize = function(path) { - private$root <- root_open(path, locate = FALSE, require_orderly = FALSE) + private$root <- root_open(path, require_orderly = FALSE) }, list = function() { diff --git a/R/outpack_checksum.R b/R/outpack_checksum.R index b213e35a..8c6b8f0b 100644 --- a/R/outpack_checksum.R +++ b/R/outpack_checksum.R @@ -2,7 +2,7 @@ ## present. It might have been intended for the R-backed server, now ## defunct? outpack_checksum <- function(hash_algorithm = NULL, root = NULL) { - root <- root_open(root, locate = TRUE, require_orderly = FALSE) + root <- root_open(root, require_orderly = FALSE) hash_algorithm <- hash_algorithm %||% root$config$core$hash_algorithm ## Don't use the index ever here; we want to always read this from diff --git a/R/outpack_packet.R b/R/outpack_packet.R index 31fe8f2c..986644f0 100644 --- a/R/outpack_packet.R +++ b/R/outpack_packet.R @@ -23,7 +23,7 @@ ##' @noRd outpack_packet_start <- function(path, name, parameters = NULL, id = NULL, root = NULL) { - root <- root_open(root, locate = FALSE, require_orderly = FALSE) + root <- root_open(root, require_orderly = FALSE) assert_scalar_character(name) assert_is_directory(path) diff --git a/R/query_index.R b/R/query_index.R index 3dae3a65..efc0dca2 100644 --- a/R/query_index.R +++ b/R/query_index.R @@ -84,7 +84,7 @@ query_index <- R6::R6Class( ## help with the pulling metadata issue (as we could then control only ## pulling once in a session). new_query_index <- function(root, options) { - root <- root_open(root, locate = FALSE, require_orderly = FALSE) + root <- root_open(root, require_orderly = FALSE) if (options$pull_metadata) { orderly_location_pull_metadata(options$location, root) diff --git a/R/root.R b/R/root.R index 49bddc17..f159fdc7 100644 --- a/R/root.R +++ b/R/root.R @@ -101,7 +101,7 @@ orderly_init <- function(root = ".", path_outpack <- file.path(root, ".outpack") if (file.exists(path_outpack)) { - root <- root_open(root, locate = FALSE, require_orderly = FALSE) + root <- root_open(root, require_orderly = FALSE) root_validate_same_configuration(match.call(), config, root, environment()) } else { fs::dir_create(path_outpack) @@ -117,8 +117,7 @@ orderly_init <- function(root = ".", file.path(root$path, "orderly_config.yml")) } - root <- root_open(root, locate = FALSE, require_orderly = TRUE, - call = environment()) + root <- root_open(root, require_orderly = TRUE) invisible(root$path) } @@ -140,8 +139,7 @@ empty_config_contents <- function() { ## * also check that the outpack and orderly path are compatibible ## (this is actually quite hard to get right, but should be done ## before anything is created I think) -root_open <- function(path, locate = TRUE, require_orderly = FALSE, - call = parent.frame()) { +root_open <- function(path, require_orderly = FALSE, call = parent.frame()) { if (is.null(call)) { call <- environment() } @@ -152,15 +150,9 @@ root_open <- function(path, locate = TRUE, require_orderly = FALSE, ## This is going to error, but the error later will do. path <- path$path } - if (is.null(path)) { - path <- getwd() - locate <- locate && TRUE - } else { - locate <- FALSE - } - assert_scalar_character(path, call = call) - assert_is_directory(path, call = call) + locate <- is.null(path) if (locate) { + path <- getwd() path_outpack <- find_file_descend(".outpack", path) path_orderly <- find_file_descend("orderly_config.yml", path) has_outpack <- !is.null(path_outpack) @@ -182,6 +174,8 @@ root_open <- function(path, locate = TRUE, require_orderly = FALSE, } path_open <- path_outpack } else { + assert_scalar_character(path, call = call) + assert_is_directory(path, call = call) has_outpack <- file.exists(file.path(path, ".outpack")) has_orderly <- file.exists(file.path(path, "orderly_config.yml")) path_open <- path diff --git a/tests/testthat/helper-outpack.R b/tests/testthat/helper-outpack.R index 98789a09..948395eb 100644 --- a/tests/testthat/helper-outpack.R +++ b/tests/testthat/helper-outpack.R @@ -101,7 +101,7 @@ create_temporary_root <- function(...) { path <- tempfile() withr::defer_parent(fs::dir_delete(path)) suppressMessages(orderly_init(path, ...)) - root_open(path, locate = FALSE, require_orderly = FALSE) + root_open(path, require_orderly = FALSE) } diff --git a/tests/testthat/test-cleanup.R b/tests/testthat/test-cleanup.R index 75036ed0..0c4fb9aa 100644 --- a/tests/testthat/test-cleanup.R +++ b/tests/testthat/test-cleanup.R @@ -12,7 +12,7 @@ test_that("can cleanup explicit things quite well", { c("name", "root", "path", "role", "status", "delete", "unknown")) expect_equal(status$name, "explicit") expect_equal(normalise_path(status$root), - normalise_path(root_open(path, FALSE, FALSE)$path)) + normalise_path(root_open(path, require_orderly = FALSE)$path)) expect_equal(normalise_path(status$path), normalise_path(file.path(status$root, "src", status$name))) paths <- c("data.csv", "explicit.R", "mygraph.png") diff --git a/tests/testthat/test-init.R b/tests/testthat/test-init.R index 0cccad3b..fa11cffe 100644 --- a/tests/testthat/test-init.R +++ b/tests/testthat/test-init.R @@ -14,7 +14,7 @@ test_that("Can initialise a new orderly root", { res <- orderly_init_quietly(tmp) expect_true(file.exists(tmp)) expect_identical(normalise_path(res), normalise_path(tmp)) - root <- root_open(tmp, FALSE, TRUE) + root <- root_open(tmp, require_orderly = TRUE) expect_s3_class(root, "outpack_root") expect_equal(root$config$orderly, list(minimum_orderly_version = numeric_version("1.99.0"))) @@ -34,7 +34,7 @@ test_that("can turn an outpack root into an orderly one", { outpack_init_no_orderly(tmp) orderly_init_quietly(tmp) - root2 <- root_open(tmp, FALSE, FALSE) + root2 <- root_open(tmp, require_orderly = FALSE) expect_equal(root2$config$orderly, list(minimum_orderly_version = numeric_version("1.99.0"))) expect_s3_class(root2, "outpack_root") @@ -58,7 +58,7 @@ test_that("can initialise a repo with orderly but no .outpack directory", { i = "See ?orderly_init for more arguments to this function")) withr::with_dir(parent, orderly_init_quietly(base)) - root <- root_open(path, FALSE, TRUE) + root <- root_open(path, require_orderly = TRUE) expect_true(is_directory(file.path(path, ".outpack"))) id <- withr::with_dir(parent, diff --git a/tests/testthat/test-location.R b/tests/testthat/test-location.R index 114a4c26..827effca 100644 --- a/tests/testthat/test-location.R +++ b/tests/testthat/test-location.R @@ -210,16 +210,16 @@ test_that("re-adding a location de-orphans packets", { expect_message(orderly_location_remove("b", root = root$a), "Orphaning 2 packets") - expect_equal(nrow(root_open(root$a, FALSE)$index$location(orphan)), 2) + expect_equal(nrow(root_open(root$a)$index$location(orphan)), 2) expect_message(orderly_location_remove("c", root = root$a), "Orphaning 3 packets") - expect_equal(nrow(root_open(root$a, FALSE)$index$location(orphan)), 5) + expect_equal(nrow(root_open(root$a)$index$location(orphan)), 5) orderly_location_add("b", "path", list(path = root$b), root = root$a) expect_message(orderly_location_pull_metadata(root = root$a), "De-orphaning 2 packets") - expect_equal(nrow(root_open(root$a, FALSE)$index$location(orphan)), 3) + expect_equal(nrow(root_open(root$a)$index$location(orphan)), 3) }) diff --git a/tests/testthat/test-outpack-root.R b/tests/testthat/test-outpack-root.R index ee252d67..c0557fc0 100644 --- a/tests/testthat/test-outpack-root.R +++ b/tests/testthat/test-outpack-root.R @@ -23,18 +23,18 @@ test_that("Can locate an outpack root", { expect_equal( withr::with_dir( p, - root_open(NULL, locate = TRUE, require_orderly = FALSE)$path), - root_open(path, locate = FALSE, require_orderly = FALSE)$path) + root_open(NULL, require_orderly = FALSE)$path), + root_open(path, require_orderly = FALSE)$path) expect_identical( - root_open(root, locate = FALSE, require_orderly = FALSE), root) + root_open(root, require_orderly = FALSE), root) }) test_that("root_open errors if it reaches toplevel", { - path <- temp_file() - fs::dir_create(path) + path <- withr::local_tempdir() expect_error( - root_open(path, locate = TRUE, require_orderly = FALSE), + withr::with_dir(path, + root_open(NULL, require_orderly = FALSE)), "Did not find existing orderly (or outpack) root in", fixed = TRUE) }) @@ -44,16 +44,16 @@ test_that("root_open does not recurse if locate = FALSE", { root <- create_temporary_root() path <- root$path expect_identical( - root_open(root, locate = FALSE, require_orderly = FALSE), + root_open(root, require_orderly = FALSE), root) expect_equal( - root_open(path, locate = FALSE, require_orderly = FALSE)$path, + root_open(path, require_orderly = FALSE)$path, path) p <- file.path(path, "a", "b", "c") fs::dir_create(p) expect_error( - root_open(p, locate = FALSE, require_orderly = FALSE), + root_open(p, require_orderly = FALSE), "Did not find existing orderly (or outpack) root in", fixed = TRUE) }) @@ -87,7 +87,7 @@ test_that("can find appropriate root if in working directory with path NULL", { root <- create_temporary_root() res <- withr::with_dir( root$path, - root_open(NULL, locate = TRUE, require_orderly = FALSE)) + root_open(NULL, require_orderly = FALSE)) expect_equal(res$path, root$path) }) diff --git a/tests/testthat/test-plugin.R b/tests/testthat/test-plugin.R index f894df73..5b81c21a 100644 --- a/tests/testthat/test-plugin.R +++ b/tests/testthat/test-plugin.R @@ -60,7 +60,7 @@ test_that("Can use custom deserialiser plugin", { meta <- orderly_metadata(id, root = path) - root <- root_open(path, locate = FALSE, require_orderly = FALSE) + root <- root_open(path, require_orderly = FALSE) meta <- orderly_metadata(id, root = root) expect_s3_class(meta$custom$example.random, "data.frame") expect_equal(meta$custom$example.random, diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index d1ff24df..4b83f4b9 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -24,7 +24,7 @@ test_that("error of opening an outpack root that is not an orderly root", { root <- outpack_init_no_orderly(tmp) err <- expect_error( - withr::with_dir(tmp, root_open(".", FALSE, TRUE)), + withr::with_dir(tmp, root_open(".", require_orderly = TRUE)), "Did not find 'orderly_config.yml' in '.", fixed = TRUE) expect_equal( @@ -41,13 +41,16 @@ test_that("pass back a root", { path_outpack <- withr::local_tempfile() root_outpack <- outpack_init_no_orderly(path_outpack) path_orderly <- test_prepare_orderly_example(character()) - root_orderly <- root_open(path_orderly, FALSE, TRUE) - - expect_identical(root_open(root_orderly, FALSE, FALSE), root_orderly) - expect_identical(root_open(root_orderly, FALSE, TRUE), root_orderly) - expect_identical(root_open(root_outpack, FALSE, FALSE), root_outpack) + root_orderly <- root_open(path_orderly, require_orderly = TRUE) + + expect_identical(root_open(root_orderly, require_orderly = FALSE), + root_orderly) + expect_identical(root_open(root_orderly, require_orderly = TRUE), + root_orderly) + expect_identical(root_open(root_outpack, require_orderly = FALSE), + root_outpack) expect_error( - root_open(root_outpack, FALSE, TRUE), + root_open(root_outpack, require_orderly = TRUE), sprintf("Did not find 'orderly_config.yml' in '%s'", root_outpack$path)) }) @@ -149,7 +152,7 @@ test_that("can identify a plain source root", { test_that("can identify a plain source root from a full root", { path <- test_prepare_orderly_example("explicit") - root <- root_open(path, FALSE) + root <- root_open(path) expect_equal(orderly_src_root(root$path, FALSE), root$path) expect_equal(orderly_src_root(root, FALSE), root$path) }) diff --git a/tests/testthat/test-run.R b/tests/testthat/test-run.R index 122125f5..4a5bbe80 100644 --- a/tests/testthat/test-run.R +++ b/tests/testthat/test-run.R @@ -985,7 +985,7 @@ test_that("nice error if running nonexistant report", { test_that("validation of orderly directories", { path <- test_prepare_orderly_example(character()) - root <- root_open(path, FALSE, TRUE) + root <- root_open(path, require_orderly = TRUE) nms <- sprintf("example_%s", letters[1:8]) fs::dir_create(file.path(path, "src", nms)) file.create(file.path(path, "src", nms, sprintf("%s.R", nms))) @@ -1041,7 +1041,7 @@ test_that("validation of orderly directories", { test_that("strip extraneous path components from orderly path", { path <- test_prepare_orderly_example(character()) - root <- root_open(path, FALSE, TRUE) + root <- root_open(path, require_orderly = TRUE) fs::dir_create(file.path(path, "src", "example_a")) file.create(file.path(path, "src", "example_a", "example_a.R"))