Skip to content

Commit

Permalink
Merge pull request #122 from mrc-ide/mrc-4969
Browse files Browse the repository at this point in the history
Mrc 4969 Allow <reportname>.R or orderly.R as orderly file
  • Loading branch information
r-ash authored Feb 29, 2024
2 parents d174d41 + ae37530 commit 4a060c1
Show file tree
Hide file tree
Showing 47 changed files with 335 additions and 230 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: orderly2
Title: Orderly Next Generation
Version: 1.99.11
Version: 1.99.12
Authors@R: c(person("Rich", "FitzJohn", role = c("aut", "cre"),
email = "[email protected]"),
person("Robert", "Ashton", role = "aut"),
Expand Down
5 changes: 3 additions & 2 deletions R/cleanup.R
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@
##' # We simulate running a packet interactively by using 'source';
##' # you might have run this line-by-line, or with the "Source"
##' # button in Rstudio.
##' source(file.path(path, "src/data/orderly.R"), chdir = TRUE)
##' source(file.path(path, "src/data/data.R"), chdir = TRUE)
##'
##' # Having run this, the output of the report is present in the
##' # source directory:
Expand Down Expand Up @@ -137,8 +137,9 @@ orderly_cleanup_status <- function(name = NULL, root = NULL, locate = TRUE) {
nms_artefact <- unlist(lapply(info$artefacts, "[[", "files"))
nms_dependency <- unlist(lapply(info$dependency, function(x) names(x$files)))
nms_shared_resource <- names(info$shared_resource)
entrypoint_filename <- find_entrypoint_filename(path)

role <- cbind(orderly = files == "orderly.R",
role <- cbind(orderly = files == entrypoint_filename,
resource = matches_path(files, nms_resource),
shared_resource = matches_path(files, nms_shared_resource),
dependency = matches_path(files, nms_dependency, FALSE),
Expand Down
2 changes: 1 addition & 1 deletion R/gitignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ gitignore_content_root <- function(root_path) {


gitignore_content_src <- function(name, root_path) {
dat <- orderly_read_r(file.path(root_path, "src", name, "orderly.R"))
dat <- orderly_read(file.path(root_path, "src", name))

ignore_deps <- unlist(lapply(dat$dependency, function(x) names(x$files)))
ignore_artefacts <- unlist(lapply(dat$artefacts, "[[", "files"))
Expand Down
6 changes: 4 additions & 2 deletions R/metadata.R
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ static_orderly_strict_mode <- function(args) {
##' @section Behaviour in interactive sessions:
##'
##' When running interactively (i.e., via `source()` or running an
##' `orderly.R` session by copy/paste or in Rstudio), the
##' orderly file session by copy/paste or in Rstudio), the
##' `orderly_parameters()` function has different behaviour.
##'
##' First, we look in the current environment (most likely the global
Expand Down Expand Up @@ -452,9 +452,11 @@ get_active_packet <- function() {

prevent_multiple_calls <- function(packet, name, call) {
if (!is.null(packet$orderly2[[name]])) {
entrypoint_filename <- find_entrypoint_filename(packet$orderly2$src)
cli::cli_abort(
c("Only one call to 'orderly2::orderly_{name}' is allowed",
i = "You have already called this function earlier in your orderly.R"),
i = paste("You have already called this function earlier",
"in your {entrypoint_filename}")),
call = call)
}
}
29 changes: 20 additions & 9 deletions R/orderly.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
##' List source reports - that is, directories within `src/` that
##' contain a file `orderly.R`
##' look suitable for running with orderly; these will be directories
##' that contain an entrypoint file - a `.R` file with the same name
##' as the directory (e.g., `src/data/data.R` corresponds to `data`).
##'
##' @title List source reports
##'
Expand All @@ -21,7 +23,11 @@ orderly_list_src <- function(root = NULL, locate = TRUE) {
return(character())
}
pos <- fs::dir_ls(file.path(root_path, "src"), type = "directory")
basename(pos)[file_exists(file.path(pos, "orderly.R"))]
entrypoint <- vcapply(pos, function(path) {
find_entrypoint_filename(path, suppress_zero_files = TRUE,
suppress_multiple_files = TRUE)
})
basename(pos)[!is.na(entrypoint)]
}


Expand All @@ -36,7 +42,7 @@ orderly_list_src <- function(root = NULL, locate = TRUE) {
##' suppresses any default content. We may support customisable
##' templates in future - let us know if this would be useful.
##'
##' @param force Create an `orderly.R` file within an existing
##' @param force Create an orderly file - `<name>.R` within an existing
##' directory `src/<name>`; this may be useful if you have already
##' created the directory and some files first but want help
##' creating the orderly file.
Expand All @@ -49,9 +55,13 @@ orderly_new <- function(name, template = NULL, force = FALSE,
root = NULL, locate = TRUE) {
root <- root_open(root, locate, require_orderly = TRUE, call = environment())
dest <- file.path(root$path, "src", name)
existing_entrypoint_filename <- find_entrypoint_filename(
dest, suppress_zero_files = TRUE
)
new_report_filename <- sprintf("%s.R", name)

if (file.exists(file.path(dest, "orderly.R"))) {
cli::cli_abort("'src/{name}/orderly.R' already exists")
if (!is.na(existing_entrypoint_filename)) {
cli::cli_abort("'src/{name}/{existing_entrypoint_filename}' already exists")
}
if (file.exists(dest) && !fs::is_dir(dest)) {
cli::cli_abort(
Expand All @@ -61,8 +71,9 @@ orderly_new <- function(name, template = NULL, force = FALSE,
if (length(dir(dest, all.files = TRUE, no.. = TRUE)) > 0 && !force) {
cli::cli_abort(
c("'src/{name}/' already exists and contains files",
i = paste("If you want to add an orderly.R to this directory,",
"rerun {.code orderly_new()} with {.code force = TRUE}")))
i = paste("If you want to add a {new_report_filename} to this",
"directory, rerun {.code orderly_new()} with",
"{.code force = TRUE}")))
}

if (is.null(template)) {
Expand All @@ -74,6 +85,6 @@ orderly_new <- function(name, template = NULL, force = FALSE,
}

fs::dir_create(dest)
writeLines(contents, file.path(dest, "orderly.R"))
cli::cli_alert_success("Created 'src/{name}/orderly.R'")
writeLines(contents, file.path(dest, new_report_filename))
cli::cli_alert_success("Created 'src/{name}/{new_report_filename}'")
}
2 changes: 1 addition & 1 deletion R/plugin.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
##' Create an orderly plugin. A plugin is typically defined by a
##' package and is used to extend orderly by enabling new
##' functionality, declared in `orderly_config.yml` and `orderly.R`
##' functionality, declared in `orderly_config.yml` and your orderly file,
##' and affecting the running of reports primarily by creating new
##' objects in the report environment. This system is discussed in
##' more detail in `vignette("plugins")`, but will be expanded (likely
Expand Down
14 changes: 7 additions & 7 deletions R/read.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,10 @@
orderly_read <- function(path, call = NULL) {
assert_file_exists_relative("orderly.R", name = "Orderly file",
workdir = path, call = call)
orderly_read_r(file.path(path, "orderly.R"))
entrypoint_filename <- find_entrypoint_filename(path)
orderly_read_r(file.path(path, entrypoint_filename), entrypoint_filename)
}


orderly_read_r <- function(path) {
orderly_read_r <- function(path, entrypoint_filename) {
exprs <- parse(file = path)

inputs <- list()
Expand Down Expand Up @@ -51,7 +50,7 @@ orderly_read_r <- function(path) {
## Rename to make things easier below:
names(dat) <- sub("^orderly_", "", names(dat))

ret <- list()
ret <- list(entrypoint_filename = entrypoint_filename)
if (length(dat$strict_mode) > 0) {
ret$strict <- dat$strict_mode[[1]]
} else {
Expand All @@ -72,11 +71,12 @@ orderly_read_r <- function(path) {
## TODO: probably some santisiation required here:
##
## * what do we do with directories here?
## * discourage people from listing orderly.R
## * discourage people from listing orderly files
## * discourage duplicates

if (length(dat$resource) > 0) {
ret$resources <- setdiff(unique(unlist(dat$resource, TRUE, FALSE)),
"orderly.R")
entrypoint_filename)
}
if (length(dat$artefact) > 0) {
ret$artefacts <- dat$artefact
Expand Down
53 changes: 31 additions & 22 deletions R/run.R
Original file line number Diff line number Diff line change
Expand Up @@ -177,6 +177,7 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,

src <- file.path(root_src, "src", name)
dat <- orderly_read(src, environment())
entrypoint_filename <- dat$entrypoint_filename
parameters <- check_parameters(parameters, dat$parameters, environment())
orderly_validate(dat, src)

Expand All @@ -194,14 +195,14 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,

if (dat$strict$enabled) {
inputs_info <- NULL
fs::file_copy(file.path(src, "orderly.R"), path)
fs::file_copy(file.path(src, entrypoint_filename), path)
} else {
inputs_info <- copy_resources_implicit(src, path, dat$resources,
dat$artefacts)
}
p <- outpack_packet_start(path, name, parameters = parameters,
id = id, root = root)
outpack_packet_file_mark(p, "orderly.R", "immutable")
outpack_packet_file_mark(p, entrypoint_filename, "immutable")
p$orderly2 <- list(config = root$config$orderly, envir = envir, src = src,
root = root_src, strict = dat$strict,
inputs_info = inputs_info, search_options = search_options)
Expand All @@ -216,7 +217,7 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,
local <- new.env(parent = emptyenv())
local$warnings <- collector()
res <- rlang::try_fetch(
withr::with_dir(path, source_echo("orderly.R", envir, echo)),
withr::with_dir(path, source_echo(entrypoint_filename, envir, echo)),
warning = function(e) {
local$warnings$add(e)
rlang::zap()
Expand All @@ -233,9 +234,9 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,
success <- is.null(local$error) && info_end$success

if (success) {
cli::cli_alert_success("Finished running {.file orderly.R}")
cli::cli_alert_success("Finished running {.file {entrypoint_filename}}")
} else {
cli::cli_alert_danger("Error running {.file orderly.R}")
cli::cli_alert_danger("Error running {.file {entrypoint_filename}}")
}

if (length(local$warnings$get()) > 0) {
Expand Down Expand Up @@ -265,9 +266,10 @@ orderly_run <- function(name, parameters = NULL, envir = NULL, echo = TRUE,


custom_metadata <- function(dat) {
entrypoint_filename <- find_entrypoint_filename(dat$src)
shared <- dat$shared_resources %||% list()
role <- data_frame(
path = c("orderly.R", dat$resources, shared$here),
path = c(entrypoint_filename, dat$resources, shared$here),
role = c("orderly",
rep_along("resource", dat$resources),
rep_along("shared", shared$here)))
Expand Down Expand Up @@ -517,24 +519,27 @@ orderly_packet_add_metadata <- function(p) {

validate_orderly_directory <- function(name, root_path, call) {
assert_scalar_character(name, call = call)

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)
err <- sprintf("Did not find orderly report '%s'", name)
if (!file_exists(src)) {
detail <- sprintf("The path 'src/%s' does not exist", name)
} else if (is_directory(src)) {
detail <- sprintf(
"The path 'src/%s' exists but does not contain 'orderly.R'",
name)
} else {
detail <- sprintf(
"The path 'src/%s' exists but is not a directory",
name)
}
err <- c(err, x = detail)
src <- file.path(root_path, "src", name)

is_error <- FALSE
if (!file_exists(src)) {
is_error <- TRUE
detail <- sprintf("The path 'src/%s' does not exist", name)
} else if (!is_directory(src)) {
is_error <- TRUE
detail <- sprintf(
"The path 'src/%s' exists but is not a directory",
name
)
}

if (is_error) {
err <- c(
sprintf("Did not find orderly report '%s'", name),
x = detail
)
near <- near_match(name, orderly_list_src(root_path, FALSE))
if (length(near) > 0) {
hint <- sprintf("Did you mean %s",
Expand All @@ -546,6 +551,10 @@ validate_orderly_directory <- function(name, root_path, call) {
cli::cli_abort(err, call = call)
}

# Just being called for the deprecation warning
# Should be removed once we deprecate the name
find_entrypoint_filename(file.path(root_path, "src", name))

name
}

Expand Down
30 changes: 30 additions & 0 deletions R/util_assert.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,36 @@ assert_file_exists <- function(files, name = "File", call = NULL, arg = NULL) {
}


find_entrypoint_filename <- function(src, suppress_zero_files = FALSE,
suppress_multiple_files = FALSE) {
reportname <- basename(src)
names <- c(sprintf("%s.R", reportname), "orderly.R")
files_exist <- file.exists(file.path(src, names))
n_found <- sum(files_exist)
if (n_found > 1 && !suppress_multiple_files) {
cli::cli_abort(
paste("Please only create {names[[1]]} file, orderly.R",
"has been deprecated")
)
}
if (n_found == 0 && !suppress_zero_files) {
cli::cli_abort(
"Please create {names[[1]]} file"
)
}
if (files_exist[[2]]) {
cli::cli_warn(
paste("Naming convention orderly.R will be deprecated",
"soon. Please change orderly file name to",
"<reportname>.R"),
.frequency = "regularly",
.frequency_id = "deprecate_orderly_file_name"
)
}
if (n_found == 1) names[files_exist] else NA_character_
}


assert_file_exists_relative <- function(files, workdir, name, call = NULL) {
assert_relative_path(files, name, workdir, call)

Expand Down
2 changes: 1 addition & 1 deletion _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ reference:
- orderly_list_src
- title: From within a running report
desc: >-
These are the functions that get called from your `orderly.R` file
These are the functions that get called from your orderly file
contents:
- orderly_strict_mode
- orderly_parameters
Expand Down
File renamed without changes.
2 changes: 1 addition & 1 deletion man/orderly_cleanup.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 3 additions & 1 deletion man/orderly_list_src.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/orderly_new.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/orderly_parameters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions man/orderly_plugin_register.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

File renamed without changes.
File renamed without changes.
3 changes: 3 additions & 0 deletions tests/testthat/examples/deprecated-orderly-name/orderly.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
orderly2::orderly_artefact("Some data", "data.rds")
d <- data.frame(a = 1:10, x = runif(10), y = 1:10 + runif(10))
saveRDS(d, "data.rds")
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
3 changes: 3 additions & 0 deletions tests/testthat/examples/two-orderly-files/orderly.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
orderly2::orderly_artefact("Some data", "data.rds")
d <- data.frame(a = 1:10, x = runif(10), y = 1:10 + runif(10))
saveRDS(d, "data.rds")
Loading

0 comments on commit 4a060c1

Please sign in to comment.