Skip to content

Commit

Permalink
Allow for the two root types to be referenced separately
Browse files Browse the repository at this point in the history
  • Loading branch information
richfitz committed Sep 21, 2023
1 parent 254b829 commit 7920c56
Show file tree
Hide file tree
Showing 12 changed files with 100 additions and 74 deletions.
12 changes: 5 additions & 7 deletions R/cleanup.R
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down Expand Up @@ -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,
Expand Down
6 changes: 2 additions & 4 deletions R/context.R
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
36 changes: 20 additions & 16 deletions R/gitignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -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"))
Expand All @@ -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, "")
Expand All @@ -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"))
}

Expand All @@ -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)
}
Expand Down
3 changes: 1 addition & 2 deletions R/interactive.R
Original file line number Diff line number Diff line change
Expand Up @@ -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, "../..")))
}


Expand Down
2 changes: 1 addition & 1 deletion R/location.R
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
7 changes: 3 additions & 4 deletions R/orderly.R
Original file line number Diff line number Diff line change
Expand Up @@ -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"))]
}
28 changes: 27 additions & 1 deletion R/root.R
Original file line number Diff line number Diff line change
Expand Up @@ -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(
Expand Down Expand Up @@ -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)
Expand Down
21 changes: 12 additions & 9 deletions R/run.R
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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)
Expand All @@ -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)
}

Expand Down
10 changes: 5 additions & 5 deletions tests/testthat/test-gitignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -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'")
Expand All @@ -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)),
Expand All @@ -157,22 +157,22 @@ 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"))
})


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


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")
})
3 changes: 1 addition & 2 deletions tests/testthat/test-interactive.R
Original file line number Diff line number Diff line change
Expand Up @@ -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)
})
2 changes: 1 addition & 1 deletion tests/testthat/test-root.R
Original file line number Diff line number Diff line change
Expand Up @@ -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"))
Expand Down
Loading

0 comments on commit 7920c56

Please sign in to comment.