Skip to content

Commit

Permalink
Tidy up orderly_parse interface, add some validation
Browse files Browse the repository at this point in the history
  • Loading branch information
r-ash committed Mar 4, 2024
1 parent 0665401 commit ee5d7e6
Show file tree
Hide file tree
Showing 3 changed files with 58 additions and 20 deletions.
40 changes: 30 additions & 10 deletions R/read.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
orderly_read <- function(path, call = NULL) {
entrypoint_filename <- find_entrypoint_filename(path)
orderly_parse(file.path(path, entrypoint_filename), entrypoint_filename)
orderly_parse(file.path(path, entrypoint_filename))
}


Expand All @@ -12,18 +12,38 @@ orderly_read <- function(path, call = NULL) {
#' the parsed AST from an orderly script, parses details
#' of any calls to the orderly_ in-script functions into intermediate
#' representation for downstream use. Also validates that any calls to
#' orderly_ in-script functions are well-formed.
#' `orderly_*` in-script functions are well-formed.
#'
#' @param entrypoint_script Path to script or parsed AST from orderly script
#' @param entrypoint_filename Name of entrypoint file to include in metadata
#' @param path Path to `orderly_*` script
#' @param exprs Parsed AST from `orderly_*` script
#' @param filename Name of `orderly_*` file to include in metadata, required if
#' calling with `exprs`. If called with a `path` this can be NULL.
#'
#' @return Parsed orderly entrypoint script
#' @export
orderly_parse <- function(entrypoint_script, entrypoint_filename) {
if (!is.expression(entrypoint_script)) {
exprs <- parse(file = entrypoint_script)
orderly_parse <- function(path, exprs = NULL, filename = NULL) {
path_missing <- missing(path)
exprs_missing <- missing(exprs)
if ((path_missing && exprs_missing) ||
(!path_missing && !exprs_missing)) {
cli::cli_abort(c("One and only one of 'path' and 'exprs' must be set.",
i = "See {.fun orderly2::orderly_parse} for details."))
}
if (is.null(filename)) {
if (!path_missing) {
filename <- basename(path)
} else {
cli::cli_abort(c(paste(
"`filename` must be set if calling",
"{.fun orderly2::orderly_parse} with `exprs`"),
i = "See {.fun orderly2::orderly_parse} for details."))
}
}
if (!path_missing) {
assert_file_exists(path)
exprs <- parse(file = path)
} else {
exprs <- entrypoint_script
assert_is(exprs, "expression")
}

inputs <- list()
Expand Down Expand Up @@ -69,7 +89,7 @@ orderly_parse <- function(entrypoint_script, entrypoint_filename) {
## Rename to make things easier below:
names(dat) <- sub("^orderly_", "", names(dat))

ret <- list(entrypoint_filename = entrypoint_filename)
ret <- list(entrypoint_filename = filename)
if (length(dat$strict_mode) > 0) {
ret$strict <- dat$strict_mode[[1]]
} else {
Expand All @@ -95,7 +115,7 @@ orderly_parse <- function(entrypoint_script, entrypoint_filename) {

if (length(dat$resource) > 0) {
ret$resources <- setdiff(unique(unlist(dat$resource, TRUE, FALSE)),
entrypoint_filename)
filename)
}
if (length(dat$artefact) > 0) {
ret$artefacts <- dat$artefact
Expand Down
11 changes: 7 additions & 4 deletions man/orderly_parse.Rd

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

27 changes: 21 additions & 6 deletions tests/testthat/test-read.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
test_that("can parse file with no helpers", {
expect_equal(orderly_parse("examples/implicit/implicit.R", "implicit.R"),
expect_equal(orderly_parse("examples/implicit/implicit.R"),
list(entrypoint_filename = "implicit.R",
strict = list(enabled = FALSE)))
})


test_that("can parse file with helpers", {
dat <- orderly_parse("examples/explicit/explicit.R", "explicit.R")
dat <- orderly_parse("examples/explicit/explicit.R")
expect_setequal(names(dat),
c("entrypoint_filename", "strict", "resources", "artefacts"))
expect_equal(dat$strict, list(enabled = FALSE))
Expand All @@ -19,14 +19,29 @@ test_that("can parse file with helpers", {

test_that("can parse file from expression", {
exprs <- parse(file = "examples/explicit/explicit.R")
dat <- orderly_parse(exprs, "explicit.R")
expect_equal(dat, orderly_parse("examples/explicit/explicit.R", "explicit.R"))
dat <- orderly_parse(exprs = exprs, filename = "explicit.R")
expect_equal(dat, orderly_parse("examples/explicit/explicit.R"))
})



test_that("useful error raised if trying to parse from path and exprs", {
expect_error(orderly_parse(path = "p", exprs = "e"),
"One and only one of 'path' and 'exprs' must be set.")
expect_error(orderly_parse(),
"One and only one of 'path' and 'exprs' must be set.")
})


test_that("useful error raised if trying to parse with exprs and no filename", {
exprs <- parse(file = "examples/explicit/explicit.R")
expect_error(orderly_parse(exprs = exprs),
"`filename` must be set if calling")
})


test_that("Skip over computed resources", {
dat <- orderly_parse("examples/computed-resource/computed-resource.R",
"computed-resource.R")
dat <- orderly_parse("examples/computed-resource/computed-resource.R")
expect_null(dat$resources)
})

Expand Down

0 comments on commit ee5d7e6

Please sign in to comment.