From 1acffd89a61605a024285ac7592aff3ecbcbc75f Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Tue, 4 Jul 2023 16:51:00 +0100 Subject: [PATCH 1/9] wip --- DESCRIPTION | 5 +++ R/helper.R | 88 +++++++++++++++++++++++++++++++++++++++++++++++++++++ README.md | 16 ++++++++++ tmp.R | 1 + 4 files changed, 110 insertions(+) create mode 100644 R/helper.R create mode 100644 tmp.R diff --git a/DESCRIPTION b/DESCRIPTION index 913b0fb..50335ad 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -12,6 +12,11 @@ Roxygen: list(markdown = TRUE) RoxygenNote: 7.1.1 URL: https://github.com/mrc-ide/orderly.helper BugReports: https://github.com/mrc-ide/orderly.helper/issues +Imports: + pkgload, + yaml Suggests: + orderly1, + orderly2, testthat (>= 3.0.0) Config/testthat/edition: 3 diff --git a/R/helper.R b/R/helper.R new file mode 100644 index 0000000..a37d401 --- /dev/null +++ b/R/helper.R @@ -0,0 +1,88 @@ +##' Activate orderly for the current repository. +##' +##' @title Activate orderly for current reposotory +##' @return +##' @author Richard Fitzjohn +activate <- function() { + ## read back to find orderly_config.yml + ## read version + ## activate correct version +} + + +activate_orderly1 <- function() { + orderly_ns_env("orderly1") +} + + +activate_orderly2 <- function() { + orderly_ns_env("orderly2") +} + + +orderly_ns_env <- function(name_real) { + name <- "orderly" + env_real <- pkgload:::ns_env(name_real) + if (pkgload:::is_loaded(name)) { + rlang::env_unlock(pkgload:::ns_env(name)) + } else { + path_real <- find.package(name_real) + version <- packageVersion(name_real) + env <- pkgload:::makeNamespace(name, version) + methods::setPackageName(name, env) + pkgload:::create_dev_meta(name) + setNamespaceInfo(env, "path", path_real) + pkgload:::setup_ns_imports(path_real) + } + env <- pkgload:::ns_env(name) + exports <- names(env_real) + namespaceExport(env, exports) + ## for (nm in exports) { + ## env[[nm]] <- env_real[[nm]] + ## lockBinding(nm, env) + ## } + ## lockEnvironment(env) + env +} + + + + + + + +## orderly cannot exist: require that people have not installed it, +## and definitely not loaded it. + +sitrep <- function() { + loaded <- loadedNamespaces() + attached <- sub("^package:", "", search()) + + + f <- function(p) { + version <- tryCatch(utils::packageVersion(p), error = function(e) NULL) + list(name = p, + version = version, + is_installed = !is.null(version), + is_loaded = p %in% loaded, + is_attached = p %in% attached) + } + + pkg <- c("orderly", "orderly1", "orderly2") + ret <- lapply(pkg, f) + names(ret) <- pkg + ret +} + + +check <- function(info = sitrep()) { + if (info$orderly$is_installed) { + stop(paste("You have 'orderly' installed; please uninstall it first and", + "install 'orderly1' and/or 'orderly2' instead")) + } + if (info$orderly1$is_attached && info$orderly2$is_attached) { + stop(paste("You have 'orderly1' and 'orderly2' attached; please", + "restart your session")) + } + invisible(info) +} diff --git a/README.md b/README.md index 7ebc55d..0f3aab1 100644 --- a/README.md +++ b/README.md @@ -6,6 +6,22 @@ [![codecov.io](https://codecov.io/github/mrc-ide/orderly.helper/coverage.svg?branch=main)](https://codecov.io/github/mrc-ide/orderly.helper?branch=main) +This package exists to smooth over the difference between [`orderly1`](https://vaccineimpact.org/orderly) and [`orderly2`](https://mrc-ide.github.io/orderly2) while we manage the migration between the two packages. It will allow you to refer to either (but at the same time only *one*) of the packages by its namespace, so that + +``` +orderly::orderly_run(...) +``` + +will run `orderly_run` in one of the packages. + +Within an orderly repo, you can then run: + +``` +orderly.helper::activate() +``` + +which will configure everything for you. + ## Installation To install `orderly.helper`: diff --git a/tmp.R b/tmp.R new file mode 100644 index 0000000..b43b8cd --- /dev/null +++ b/tmp.R @@ -0,0 +1 @@ +env <- activate_orderly1() From e6d18e317e76ed2de24eae00ef848940402897a6 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Wed, 5 Jul 2023 16:37:01 +0100 Subject: [PATCH 2/9] More of interface working --- DESCRIPTION | 7 +- R/helper.R | 184 +++++++++++++++++++++++++++-------- R/util.R | 25 +++++ README.md | 20 ++++ tests/testthat/test-helper.R | 124 +++++++++++++++++++++++ 5 files changed, 316 insertions(+), 44 deletions(-) create mode 100644 tests/testthat/test-helper.R diff --git a/DESCRIPTION b/DESCRIPTION index 50335ad..e711edf 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -16,7 +16,12 @@ Imports: pkgload, yaml Suggests: + mockery, orderly1, orderly2, - testthat (>= 3.0.0) + testthat (>= 3.0.0), + withr Config/testthat/edition: 3 +Remotes: + vimc/orderly1, + mrc-ide/orderly2 diff --git a/R/helper.R b/R/helper.R index a37d401..caccc73 100644 --- a/R/helper.R +++ b/R/helper.R @@ -1,64 +1,87 @@ -##' Activate orderly for the current repository. +##' Activate orderly for the current repository. Run this from +##' anywhere within an orderly archive (i.e., a path containing +##' orderly_config.yml; or where one of its parent directories do). We +##' check what the required orderly minimum version is and set up the +##' orderly namespace for the appropriate version. ##' ##' @title Activate orderly for current reposotory -##' @return +##' @return Nothing. ##' @author Richard Fitzjohn -activate <- function() { - ## read back to find orderly_config.yml - ## read version - ## activate correct version +activate <- function(verbose = NULL) { + version <- detect_orderly_version(getwd()) + create_orderly_ns(version, verbose) } -activate_orderly1 <- function() { - orderly_ns_env("orderly1") +##' Set up orderly based on your global preferences. This will look at +##' the R option (`orderly.version`) and the environment variable +##' `ORDERLY_VERSION`, in that order, falling back on the second +##' version. Or pass in a version explicitly. +##' +##' @title Set orderly version +##' +##' @param version Either `NULL` (in which case we use global +##' preferences) or a number `1` or `2`. +##' +##' @export +##' @return Nothing, called for side effects only. +use <- function(version = NULL, verbose = NULL) { + version <- guess_orderly_version(version) + create_orderly_ns(version, verbose = NULL) } -activate_orderly2 <- function() { - orderly_ns_env("orderly2") -} - +## Persistant package state goes here +current <- new.env(parent = emptyenv()) -orderly_ns_env <- function(name_real) { - name <- "orderly" - env_real <- pkgload:::ns_env(name_real) - if (pkgload:::is_loaded(name)) { - rlang::env_unlock(pkgload:::ns_env(name)) - } else { - path_real <- find.package(name_real) - version <- packageVersion(name_real) - env <- pkgload:::makeNamespace(name, version) - methods::setPackageName(name, env) - pkgload:::create_dev_meta(name) - setNamespaceInfo(env, "path", path_real) - pkgload:::setup_ns_imports(path_real) +create_orderly_ns <- function(version, verbose) { + name <- sprintf("orderly%d", version) + verbose <- orderly_helper_verbose(verbose) + if (identical(name, current$name)) { + if (verbose) { + message(sprintf("Already using %s", orderly_version_str(version))) + } + return(invisible()) } - env <- pkgload:::ns_env(name) - exports <- names(env_real) - namespaceExport(env, exports) - ## for (nm in exports) { - ## env[[nm]] <- env_real[[nm]] - ## lockBinding(nm, env) - ## } - ## lockEnvironment(env) - env + if (verbose) { + message(sprintf("Using %s", orderly_version_str(version))) + } + path <- find.package(name) + + desc_contents <- readLines(file.path(path, "DESCRIPTION")) + i <- grep("^Package:", desc_contents) + desc_contents[[i]] <- "Package: orderly" + + exports <- getNamespaceExports(asNamespace(name)) + ns_contents <- c(sprintf('import("%s")', name), + sprintf('export("%s")', exports)) + + tmp <- temp_package_dir(name) + writeLines(desc_contents, file.path(tmp, "DESCRIPTION")) + writeLines(ns_contents, file.path(tmp, "NAMESPACE")) + res <- pkgload::load_all(tmp, attach = FALSE, quiet = !verbose) + + ## Lastly, we might wire up the help too: + ## + ## pkgload:::dev_help(topic_str, package_str) -> + ## utils::help(topic_str, "orderly1") + ## + ## also system.file and vignette need dealing with; these might be + ## somewhat trickier though, and devtools/pkgload don't try and pull + ## it off, so we can't rely on assistance there. + ## + ## Also don't support ':::' access; that's reasonable though. + + current$name <- name + + invisible() } - - - - - -## orderly cannot exist: require that people have not installed it, -## and definitely not loaded it. - sitrep <- function() { loaded <- loadedNamespaces() attached <- sub("^package:", "", search()) - f <- function(p) { version <- tryCatch(utils::packageVersion(p), error = function(e) NULL) list(name = p, @@ -86,3 +109,78 @@ check <- function(info = sitrep()) { } invisible(info) } + + +temp_package_dir <- function(name) { + if (is.null(current$path)) { + current$path <- tempfile() + } + path <- file.path(current$path, name) + dir.create(path, FALSE, TRUE) + path +} + + +orderly_helper_verbose <- function(verbose) { + verbose %||% getOption("orderly.helper.verbose", TRUE) +} + + +detect_orderly_version <- function(path) { + root <- find_orderly_root(path) + if (is.null(root)) { + stop(sprintf("Did not find orderly root above '%s'", path)) + } + d <- yaml::yaml.load_file(file.path(root, "orderly_config.yml")) + version_str <- d$minimum_orderly_version + if (is.null(version_str)) { + stop(sprintf("Failed to read required orderly version from '%s'", path)) + } + version <- numeric_version(version_str) + if (version < numeric_version("1.99.0")) 1 else 2 +} + + +guess_orderly_version <- function(version) { + if (!is.null(version)) { + version <- validate_orderly_version(version, "argument 'version'", FALSE) + } + + version <- getOption("orderly.version", NULL) + if (!is.null(version)) { + return(validate_orderly_version(version, "option 'orderly.version'")) + } + version <- Sys.getenv("ORDERLY_VERSION", NA_character_) + if (!is.na(version)) { + return(validate_orderly_version(version, + "environment variable 'ORDERLY_VERSION'", + TRUE)) + } + 2 +} + + +validate_orderly_version <- function(value, name, from_character = FALSE) { + if (from_character) { + if (!grepl("^[0-9]$", value)) { + stop(sprintf("Expected 'version' to be a number (from %s)", name)) + } + value <- as.numeric(value) + } else { + if (!(is.numeric(value) && length(value) == 1 && !is.na(value))) { + stop(sprintf("Expected 'version' to be scalar number (from %s)", name)) + } + } + if (!(value %in% 1:2)) { + stop(sprintf("Invalid version '%s', expected '1' or '2' (from %s)", + value, name)) + } + value +} + + +orderly_version_str <- function(major) { + name <- sprintf("orderly%d", major) + version <- tryCatch(utils::packageVersion(name), error = function(e) "???") + sprintf("orderly %d (%s)", major, as.character(version)) +} diff --git a/R/util.R b/R/util.R index 0354298..077fc10 100644 --- a/R/util.R +++ b/R/util.R @@ -1,3 +1,28 @@ `%||%` <- function(x, y) { # nolint if (is.null(x)) y else x } + + +find_orderly_root <- function(start) { + target <- "orderly_config.yml" + root <- normalizePath("/", mustWork = TRUE) + + f <- function(path) { + if (file.exists(file.path(path, target))) { + return(path) + } + if (normalizePath(path, mustWork = TRUE) == root) { + return(NULL) + } + parent <- normalizePath(file.path(path, "..")) + if (parent == path) { + return(NULL) + } + Recall(parent) + } + ret <- f(start) + if (!(is.null(ret))) { + ret <- normalizePath(ret, mustWork = TRUE) + } + ret +} diff --git a/README.md b/README.md index 0f3aab1..9d07658 100644 --- a/README.md +++ b/README.md @@ -22,6 +22,26 @@ orderly.helper::activate() which will configure everything for you. +Alternatively, run + +```r +orderly.helper::use() +``` + +which will set up orderly based on your personal preferences. + +We recommend adding to your `.Rprofile`: + +```{r} +options(orderly.version = 2, orderly.helper.verbose = TRUE) +if (!require("orderly.helper", quietly = TRUE)) { + tryCatch(orderly.helper::activate(), + error = function(e) orderly.helper::use()) +} +``` + +With the two options configured as you prefer. + ## Installation To install `orderly.helper`: diff --git a/tests/testthat/test-helper.R b/tests/testthat/test-helper.R new file mode 100644 index 0000000..c745ae7 --- /dev/null +++ b/tests/testthat/test-helper.R @@ -0,0 +1,124 @@ +test_that("orderly_version_str constructs good strings", { + skip_if_not_installed("mockery") + mock_package_version <- mockery::mock( + numeric_version("1.7.0"), + numeric_version("1.99.0"), + stop("package not installed")) + mockery::stub(orderly_version_str, "utils::packageVersion", + mock_package_version) + expect_equal( + orderly_version_str(1), "orderly 1 (1.7.0)") + expect_equal( + orderly_version_str(2), "orderly 2 (1.99.0)") + expect_equal( + orderly_version_str(2), "orderly 2 (???)") +}) + + +test_that("can validate orderly version", { + expect_equal(validate_orderly_version(1, "arg", FALSE), 1) + expect_equal(validate_orderly_version(2, "arg", FALSE), 2) + expect_equal(validate_orderly_version("1", "arg", TRUE), 1) + expect_equal(validate_orderly_version("2", "arg", TRUE), 2) + + expect_error(validate_orderly_version(1:2, "arg", FALSE), + "Expected 'version' to be scalar number (from arg)", + fixed = TRUE) + expect_error(validate_orderly_version("1", "arg", FALSE), + "Expected 'version' to be scalar number (from arg)", + fixed = TRUE) + expect_error(validate_orderly_version(NA_real_, "arg", FALSE), + "Expected 'version' to be scalar number (from arg)", + fixed = TRUE) + expect_error(validate_orderly_version(3, "arg", FALSE), + "Invalid version '3', expected '1' or '2' (from arg)", + fixed = TRUE) + + expect_error(validate_orderly_version("one", "arg", TRUE), + "Expected 'version' to be a number (from arg)", + fixed = TRUE) +}) + + +test_that("can guess orderly version", { + withr::local_envvar(ORDERLY_VERSION = NA) + withr::local_options(orderly.version = NULL) + expect_equal(guess_orderly_version(NULL), 2) + + expect_equal(guess_orderly_version(1), 2) + expect_equal(guess_orderly_version(2), 2) + + withr::with_options(list(orderly.version = 1), + expect_equal(guess_orderly_version(NULL), 1)) + withr::with_options(list(orderly.version = 2), + expect_equal(guess_orderly_version(NULL), 2)) + + withr::with_envvar(c(ORDERLY_VERSION = 1), { + expect_equal(guess_orderly_version(NULL), 1) + withr::with_options(list(orderly.version = 1), + expect_equal(guess_orderly_version(NULL), 1)) + withr::with_options(list(orderly.version = 2), + expect_equal(guess_orderly_version(NULL), 2)) + }) +}) + + +test_that("can respond to verbose option", { + withr::local_options(orderly.helper.verbose = NULL) + expect_true(orderly_helper_verbose(NULL)) + expect_true(orderly_helper_verbose(TRUE)) + expect_false(orderly_helper_verbose(FALSE)) + withr::with_options(list(orderly.helper.verbose = FALSE), { + expect_false(orderly_helper_verbose(NULL)) + expect_true(orderly_helper_verbose(TRUE)) + expect_false(orderly_helper_verbose(FALSE)) + }) +}) + + +test_that("can detect orderly version", { + tmp <- withr::local_tempdir() + expect_error( + detect_orderly_version(tmp), + "Did not find orderly root above") + file.create(file.path(tmp, "orderly_config.yml")) + expect_error( + detect_orderly_version(tmp), + "Failed to read required orderly version from") + writeLines("minimum_orderly_version: 1.7.0", + file.path(file.path(tmp, "orderly_config.yml"))) + expect_equal(detect_orderly_version(tmp), 1) + writeLines("minimum_orderly_version: 1.99.0", + file.path(file.path(tmp, "orderly_config.yml"))) + expect_equal(detect_orderly_version(tmp), 2) + writeLines("minimum_orderly_version: 2.0.0", + file.path(file.path(tmp, "orderly_config.yml"))) + expect_equal(detect_orderly_version(tmp), 2) +}) + + +test_that("can set up orderly1 as orderly", { + current$name <- NULL + msg <- testthat::capture_messages(create_orderly_ns(1, TRUE)) + expect_match(msg, "Using orderly 1 \\(1.\\d+.\\d+\\)", all = FALSE) + expect_identical(getExportedValue("orderly", "orderly_run"), + orderly1::orderly_run) + + msg <- testthat::capture_messages(create_orderly_ns(1, TRUE)) + expect_match(msg, "Already using orderly 1 \\(1.\\d+.\\d+\\)", all = FALSE) + expect_identical(getExportedValue("orderly", "orderly_run"), + orderly1::orderly_run) +}) + + +test_that("can set up orderly2 as orderly", { + expect_silent(create_orderly_ns(2, FALSE)) + expect_identical(getExportedValue("orderly", "orderly_run"), + orderly2::orderly_run) + + expect_silent(create_orderly_ns(2, FALSE)) + expect_identical(getExportedValue("orderly", "orderly_run"), + orderly2::orderly_run) +}) + + From 4266b0888bae5d96f8cd8a89073f63c4def419f4 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Wed, 5 Jul 2023 17:04:22 +0100 Subject: [PATCH 3/9] More testing --- R/helper.R | 81 +++++++++++++++++++++++++----------- tests/testthat/test-helper.R | 80 ++++++++++++++++++++++++++++++++++- 2 files changed, 136 insertions(+), 25 deletions(-) diff --git a/R/helper.R b/R/helper.R index caccc73..a4b42c0 100644 --- a/R/helper.R +++ b/R/helper.R @@ -27,7 +27,58 @@ activate <- function(verbose = NULL) { ##' @return Nothing, called for side effects only. use <- function(version = NULL, verbose = NULL) { version <- guess_orderly_version(version) - create_orderly_ns(version, verbose = NULL) + create_orderly_ns(version, verbose) +} + + +##' Deactivate any orderly helper +##' +##' @title Deactivate orderly helper +##' @return Nothing, called for its side effect +##' @export +deactivate <- function() { + tryCatch(pkgload::unload("orderly"), error = function(e) NULL) + current$name <- NULL + current$version <- NULL + invisible() +} + + +##' Return information about the state of orderly1, orderly2 and the helper +##' +##' @title Return information about packages +##' @return A list +##' @export +sitrep <- function() { + loaded <- loadedNamespaces() + attached <- sub("^package:", "", search()) + + f <- function(p) { + version <- tryCatch(utils::packageVersion(p), error = function(e) NULL) + list(version = version, + is_installed = !is.null(version), + is_loaded = p %in% loaded, + is_attached = p %in% attached) + } + + pkg <- c("orderly", "orderly1", "orderly2") + ret <- lapply(pkg, f) + names(ret) <- pkg + + if (ret$orderly$is_installed) { + is_installed <- any( + file.exists(file.path(.libPaths(), "orderly", "DESCRIPTION"))) + if (!is_installed) { + ret$orderly <- list(version = NULL, + is_installed = FALSE, + is_loaded = FALSE, + is_attached = FALSE) + } + } + + ret$current <- list(version = current$version, name = current$name) + + ret } @@ -35,9 +86,10 @@ use <- function(version = NULL, verbose = NULL) { current <- new.env(parent = emptyenv()) create_orderly_ns <- function(version, verbose) { + check_sitrep() name <- sprintf("orderly%d", version) verbose <- orderly_helper_verbose(verbose) - if (identical(name, current$name)) { + if (identical(version, current$version)) { if (verbose) { message(sprintf("Already using %s", orderly_version_str(version))) } @@ -73,32 +125,13 @@ create_orderly_ns <- function(version, verbose) { ## Also don't support ':::' access; that's reasonable though. current$name <- name + current$version <- version invisible() } -sitrep <- function() { - loaded <- loadedNamespaces() - attached <- sub("^package:", "", search()) - - f <- function(p) { - version <- tryCatch(utils::packageVersion(p), error = function(e) NULL) - list(name = p, - version = version, - is_installed = !is.null(version), - is_loaded = p %in% loaded, - is_attached = p %in% attached) - } - - pkg <- c("orderly", "orderly1", "orderly2") - ret <- lapply(pkg, f) - names(ret) <- pkg - ret -} - - -check <- function(info = sitrep()) { +check_sitrep <- function(info = sitrep()) { if (info$orderly$is_installed) { stop(paste("You have 'orderly' installed; please uninstall it first and", "install 'orderly1' and/or 'orderly2' instead")) @@ -143,7 +176,7 @@ detect_orderly_version <- function(path) { guess_orderly_version <- function(version) { if (!is.null(version)) { - version <- validate_orderly_version(version, "argument 'version'", FALSE) + return(validate_orderly_version(version, "argument 'version'", FALSE)) } version <- getOption("orderly.version", NULL) diff --git a/tests/testthat/test-helper.R b/tests/testthat/test-helper.R index c745ae7..2e98ef2 100644 --- a/tests/testthat/test-helper.R +++ b/tests/testthat/test-helper.R @@ -45,7 +45,7 @@ test_that("can guess orderly version", { withr::local_options(orderly.version = NULL) expect_equal(guess_orderly_version(NULL), 2) - expect_equal(guess_orderly_version(1), 2) + expect_equal(guess_orderly_version(1), 1) expect_equal(guess_orderly_version(2), 2) withr::with_options(list(orderly.version = 1), @@ -122,3 +122,81 @@ test_that("can set up orderly2 as orderly", { }) +test_that("sitrep returns useful information", { + deactivate() + ans <- sitrep() + expect_equal(ans$orderly, + list(version = NULL, + is_installed = FALSE, + is_loaded = FALSE, + is_attached = FALSE)) + expect_equal(ans$orderly1, + list(version = packageVersion("orderly1"), + is_installed = TRUE, + is_loaded = TRUE, + is_attached = FALSE)) + expect_equal(ans$orderly2, + list(version = packageVersion("orderly2"), + is_installed = TRUE, + is_loaded = TRUE, + is_attached = FALSE)) + expect_equal(ans$current, list(version = NULL, name = NULL)) +}) + + +test_that("sitrep returns useful information after helper", { + deactivate() + ans1 <- sitrep() + create_orderly_ns(2, FALSE) + ans2 <- sitrep() + expect_equal(ans2[names(ans2) != "current"], ans1[names(ans1) != "current"]) + expect_equal(ans2$current, list(version = 2, name = "orderly2")) +}) + + +test_that("sitrep check throws when expected", { + expect_silent( + check_sitrep( + list(orderly = list(is_installed = FALSE), + orderly1 = list(is_attached = FALSE), + orderly2 = list(is_attached = FALSE)))) + expect_silent( + check_sitrep( + list(orderly = list(is_installed = FALSE), + orderly1 = list(is_attached = TRUE), + orderly2 = list(is_attached = FALSE)))) + expect_silent( + check_sitrep( + list(orderly = list(is_installed = FALSE), + orderly1 = list(is_attached = FALSE), + orderly2 = list(is_attached = TRUE)))) + expect_error( + check_sitrep( + list(orderly = list(is_installed = TRUE), + orderly1 = list(is_attached = FALSE), + orderly2 = list(is_attached = FALSE))), + "You have 'orderly' installed; please uninstall it") + expect_error( + check_sitrep( + list(orderly = list(is_installed = FALSE), + orderly1 = list(is_attached = TRUE), + orderly2 = list(is_attached = TRUE))), + "You have 'orderly1' and 'orderly2' attached; please restart") +}) + + +test_that("use works with given version", { + deactivate() + use(1, FALSE) + expect_equal(current$version, 1) +}) + + +test_that("activate works with found version", { + deactivate() + tmp <- withr::local_tempdir() + writeLines("minimum_orderly_version: 1.7.0", + file.path(file.path(tmp, "orderly_config.yml"))) + withr::with_dir(tmp, activate()) + expect_equal(current$version, 1) +}) From 20e296d61580ea95c062ed9b168ca74a42a8a991 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 08:53:29 +0100 Subject: [PATCH 4/9] Use rprojroot for finding root --- DESCRIPTION | 1 + R/helper.R | 13 ++++++++++--- R/util.R | 25 ------------------------- tests/testthat/test-helper.R | 2 +- 4 files changed, 12 insertions(+), 29 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index e711edf..8c3bd48 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -13,6 +13,7 @@ RoxygenNote: 7.1.1 URL: https://github.com/mrc-ide/orderly.helper BugReports: https://github.com/mrc-ide/orderly.helper/issues Imports: + rprojroot, pkgload, yaml Suggests: diff --git a/R/helper.R b/R/helper.R index a4b42c0..74f8ca9 100644 --- a/R/helper.R +++ b/R/helper.R @@ -161,9 +161,6 @@ orderly_helper_verbose <- function(verbose) { detect_orderly_version <- function(path) { root <- find_orderly_root(path) - if (is.null(root)) { - stop(sprintf("Did not find orderly root above '%s'", path)) - } d <- yaml::yaml.load_file(file.path(root, "orderly_config.yml")) version_str <- d$minimum_orderly_version if (is.null(version_str)) { @@ -217,3 +214,13 @@ orderly_version_str <- function(major) { version <- tryCatch(utils::packageVersion(name), error = function(e) "???") sprintf("orderly %d (%s)", major, as.character(version)) } + + +find_orderly_root <- function(start) { + tryCatch( + rprojroot::find_root(rprojroot::has_file("orderly_config.yml"), + path = start), + error = function(e) { + stop(sprintf("Did not find orderly root above '%s'", start)) + }) +} diff --git a/R/util.R b/R/util.R index 077fc10..0354298 100644 --- a/R/util.R +++ b/R/util.R @@ -1,28 +1,3 @@ `%||%` <- function(x, y) { # nolint if (is.null(x)) y else x } - - -find_orderly_root <- function(start) { - target <- "orderly_config.yml" - root <- normalizePath("/", mustWork = TRUE) - - f <- function(path) { - if (file.exists(file.path(path, target))) { - return(path) - } - if (normalizePath(path, mustWork = TRUE) == root) { - return(NULL) - } - parent <- normalizePath(file.path(path, "..")) - if (parent == path) { - return(NULL) - } - Recall(parent) - } - ret <- f(start) - if (!(is.null(ret))) { - ret <- normalizePath(ret, mustWork = TRUE) - } - ret -} diff --git a/tests/testthat/test-helper.R b/tests/testthat/test-helper.R index 2e98ef2..19911ed 100644 --- a/tests/testthat/test-helper.R +++ b/tests/testthat/test-helper.R @@ -197,6 +197,6 @@ test_that("activate works with found version", { tmp <- withr::local_tempdir() writeLines("minimum_orderly_version: 1.7.0", file.path(file.path(tmp, "orderly_config.yml"))) - withr::with_dir(tmp, activate()) + withr::with_dir(tmp, activate(FALSE)) expect_equal(current$version, 1) }) From 6df414e3f725f79f17e913498c4c26ea456c3778 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 09:02:01 +0100 Subject: [PATCH 5/9] Add very lazy helper --- DESCRIPTION | 2 +- R/helper.R | 17 ++++++++++++++++- README.md | 9 +++++++-- tests/testthat/test-helper.R | 15 +++++++++++++++ 4 files changed, 39 insertions(+), 4 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 8c3bd48..f61e3b1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -9,7 +9,7 @@ Description: Only exists while we manage the migration between orderly versions. License: MIT + file LICENSE Encoding: UTF-8 Roxygen: list(markdown = TRUE) -RoxygenNote: 7.1.1 +RoxygenNote: 7.2.2 URL: https://github.com/mrc-ide/orderly.helper BugReports: https://github.com/mrc-ide/orderly.helper/issues Imports: diff --git a/R/helper.R b/R/helper.R index 74f8ca9..62a6de7 100644 --- a/R/helper.R +++ b/R/helper.R @@ -82,6 +82,21 @@ sitrep <- function() { } +##' Automatically set up the orderly namespace depending on the +##' context in which this function is called. +##' +##' If called from within an orderly repository, it will activate the +##' required version using [activate()] otherwise it will use the +##' globally preferred version with [use()] +##' +##' @title Automatically configure orderly +##' @return Nothing, called for side effects only +##' @export +auto <- function() { + tryCatch(activate(), error = function(e) use()) +} + + ## Persistant package state goes here current <- new.env(parent = emptyenv()) @@ -175,7 +190,7 @@ guess_orderly_version <- function(version) { if (!is.null(version)) { return(validate_orderly_version(version, "argument 'version'", FALSE)) } - + version <- getOption("orderly.version", NULL) if (!is.null(version)) { return(validate_orderly_version(version, "option 'orderly.version'")) diff --git a/README.md b/README.md index 9d07658..4545bb7 100644 --- a/README.md +++ b/README.md @@ -30,13 +30,18 @@ orderly.helper::use() which will set up orderly based on your personal preferences. +If you don't want to think about any of this, you can call + +```r +orderly.helper::auto() +``` + We recommend adding to your `.Rprofile`: ```{r} options(orderly.version = 2, orderly.helper.verbose = TRUE) if (!require("orderly.helper", quietly = TRUE)) { - tryCatch(orderly.helper::activate(), - error = function(e) orderly.helper::use()) + orderly.helper::auto() } ``` diff --git a/tests/testthat/test-helper.R b/tests/testthat/test-helper.R index 19911ed..b6d52c5 100644 --- a/tests/testthat/test-helper.R +++ b/tests/testthat/test-helper.R @@ -200,3 +200,18 @@ test_that("activate works with found version", { withr::with_dir(tmp, activate(FALSE)) expect_equal(current$version, 1) }) + + +test_that("auto wrapper does the right thing", { + skip_if_not_installed("mockery") + mock_activate <- mockery::mock(NULL, stop("failure")) + mock_use <- mockery::mock() + mockery::stub(auto, "activate", mock_activate) + mockery::stub(auto, "use", mock_use) + auto() + mockery::expect_called(mock_activate, 1) + mockery::expect_called(mock_use, 0) + auto() + mockery::expect_called(mock_activate, 2) + mockery::expect_called(mock_use, 1) +}) From 29c06ae691ca61510d621636a32b0609392e2f55 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 09:02:14 +0100 Subject: [PATCH 6/9] Document package --- NAMESPACE | 5 +++++ man/activate.Rd | 21 +++++++++++++++++++++ man/auto.Rd | 20 ++++++++++++++++++++ man/deactivate.Rd | 14 ++++++++++++++ man/sitrep.Rd | 14 ++++++++++++++ man/use.Rd | 21 +++++++++++++++++++++ 6 files changed, 95 insertions(+) create mode 100644 man/activate.Rd create mode 100644 man/auto.Rd create mode 100644 man/deactivate.Rd create mode 100644 man/sitrep.Rd create mode 100644 man/use.Rd diff --git a/NAMESPACE b/NAMESPACE index e651b94..8368bc9 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1 +1,6 @@ # Generated by roxygen2: do not edit by hand + +export(auto) +export(deactivate) +export(sitrep) +export(use) diff --git a/man/activate.Rd b/man/activate.Rd new file mode 100644 index 0000000..201d195 --- /dev/null +++ b/man/activate.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helper.R +\name{activate} +\alias{activate} +\title{Activate orderly for current reposotory} +\usage{ +activate(verbose = NULL) +} +\value{ +Nothing. +} +\description{ +Activate orderly for the current repository. Run this from +anywhere within an orderly archive (i.e., a path containing +orderly_config.yml; or where one of its parent directories do). We +check what the required orderly minimum version is and set up the +orderly namespace for the appropriate version. +} +\author{ +Richard Fitzjohn +} diff --git a/man/auto.Rd b/man/auto.Rd new file mode 100644 index 0000000..8c70b34 --- /dev/null +++ b/man/auto.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helper.R +\name{auto} +\alias{auto} +\title{Automatically configure orderly} +\usage{ +auto() +} +\value{ +Nothing, called for side effects only +} +\description{ +Automatically set up the orderly namespace depending on the +context in which this function is called. +} +\details{ +If called from within an orderly repository, it will activate the +required version using \code{\link[=activate]{activate()}} otherwise it will use the +globally preferred version with \code{\link[=use]{use()}} +} diff --git a/man/deactivate.Rd b/man/deactivate.Rd new file mode 100644 index 0000000..b154a7c --- /dev/null +++ b/man/deactivate.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helper.R +\name{deactivate} +\alias{deactivate} +\title{Deactivate orderly helper} +\usage{ +deactivate() +} +\value{ +Nothing, called for its side effect +} +\description{ +Deactivate any orderly helper +} diff --git a/man/sitrep.Rd b/man/sitrep.Rd new file mode 100644 index 0000000..dc2effb --- /dev/null +++ b/man/sitrep.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helper.R +\name{sitrep} +\alias{sitrep} +\title{Return information about packages} +\usage{ +sitrep() +} +\value{ +A list +} +\description{ +Return information about the state of orderly1, orderly2 and the helper +} diff --git a/man/use.Rd b/man/use.Rd new file mode 100644 index 0000000..c3085be --- /dev/null +++ b/man/use.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helper.R +\name{use} +\alias{use} +\title{Set orderly version} +\usage{ +use(version = NULL, verbose = NULL) +} +\arguments{ +\item{version}{Either \code{NULL} (in which case we use global +preferences) or a number \code{1} or \code{2}.} +} +\value{ +Nothing, called for side effects only. +} +\description{ +Set up orderly based on your global preferences. This will look at +the R option (\code{orderly.version}) and the environment variable +\code{ORDERLY_VERSION}, in that order, falling back on the second +version. Or pass in a version explicitly. +} From bd1847f275899aec3b9c2d654ab91d4ac6f26e4a Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 09:04:20 +0100 Subject: [PATCH 7/9] Documentation for all args --- R/helper.R | 6 ++++++ man/activate.Rd | 4 ++++ man/use.Rd | 3 +++ tmp.R | 1 - 4 files changed, 13 insertions(+), 1 deletion(-) delete mode 100644 tmp.R diff --git a/R/helper.R b/R/helper.R index 62a6de7..15eacbc 100644 --- a/R/helper.R +++ b/R/helper.R @@ -5,6 +5,10 @@ ##' orderly namespace for the appropriate version. ##' ##' @title Activate orderly for current reposotory +##' +##' @param verbose Be verbose about what we are doing. If `NULL` uses +##' the the value of the option `orderly.helper.verbose` +##' ##' @return Nothing. ##' @author Richard Fitzjohn activate <- function(verbose = NULL) { @@ -23,6 +27,8 @@ activate <- function(verbose = NULL) { ##' @param version Either `NULL` (in which case we use global ##' preferences) or a number `1` or `2`. ##' +##' @inheritParams activate +##' ##' @export ##' @return Nothing, called for side effects only. use <- function(version = NULL, verbose = NULL) { diff --git a/man/activate.Rd b/man/activate.Rd index 201d195..8bc5224 100644 --- a/man/activate.Rd +++ b/man/activate.Rd @@ -6,6 +6,10 @@ \usage{ activate(verbose = NULL) } +\arguments{ +\item{verbose}{Be verbose about what we are doing. If \code{NULL} uses +the the value of the option \code{orderly.helper.verbose}} +} \value{ Nothing. } diff --git a/man/use.Rd b/man/use.Rd index c3085be..842b52a 100644 --- a/man/use.Rd +++ b/man/use.Rd @@ -9,6 +9,9 @@ use(version = NULL, verbose = NULL) \arguments{ \item{version}{Either \code{NULL} (in which case we use global preferences) or a number \code{1} or \code{2}.} + +\item{verbose}{Be verbose about what we are doing. If \code{NULL} uses +the the value of the option \code{orderly.helper.verbose}} } \value{ Nothing, called for side effects only. diff --git a/tmp.R b/tmp.R deleted file mode 100644 index b43b8cd..0000000 --- a/tmp.R +++ /dev/null @@ -1 +0,0 @@ -env <- activate_orderly1() From 684460fc0af4ebfe83c6bbdb99da7e37c0da8b56 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 09:09:31 +0100 Subject: [PATCH 8/9] Use branch pin for now --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index f61e3b1..7a058eb 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -24,5 +24,5 @@ Suggests: withr Config/testthat/edition: 3 Remotes: - vimc/orderly1, + orderly1=vimc/orderly@vimc-7135, mrc-ide/orderly2 From dadd4e56ae481f4667069a36f6751c5625c69965 Mon Sep 17 00:00:00 2001 From: Rich FitzJohn Date: Thu, 6 Jul 2023 10:20:14 +0100 Subject: [PATCH 9/9] Export activate too --- DESCRIPTION | 2 +- NAMESPACE | 1 + R/helper.R | 4 ++-- man/activate.Rd | 5 +---- 4 files changed, 5 insertions(+), 7 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 7a058eb..217465b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -9,7 +9,7 @@ Description: Only exists while we manage the migration between orderly versions. License: MIT + file LICENSE Encoding: UTF-8 Roxygen: list(markdown = TRUE) -RoxygenNote: 7.2.2 +RoxygenNote: 7.2.3 URL: https://github.com/mrc-ide/orderly.helper BugReports: https://github.com/mrc-ide/orderly.helper/issues Imports: diff --git a/NAMESPACE b/NAMESPACE index 8368bc9..f5ddedc 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,5 +1,6 @@ # Generated by roxygen2: do not edit by hand +export(activate) export(auto) export(deactivate) export(sitrep) diff --git a/R/helper.R b/R/helper.R index 15eacbc..da6ed6d 100644 --- a/R/helper.R +++ b/R/helper.R @@ -9,8 +9,8 @@ ##' @param verbose Be verbose about what we are doing. If `NULL` uses ##' the the value of the option `orderly.helper.verbose` ##' -##' @return Nothing. -##' @author Richard Fitzjohn +##' @return Nothing, called for side effects only. +##' @export activate <- function(verbose = NULL) { version <- detect_orderly_version(getwd()) create_orderly_ns(version, verbose) diff --git a/man/activate.Rd b/man/activate.Rd index 8bc5224..13e1638 100644 --- a/man/activate.Rd +++ b/man/activate.Rd @@ -11,7 +11,7 @@ activate(verbose = NULL) the the value of the option \code{orderly.helper.verbose}} } \value{ -Nothing. +Nothing, called for side effects only. } \description{ Activate orderly for the current repository. Run this from @@ -20,6 +20,3 @@ orderly_config.yml; or where one of its parent directories do). We check what the required orderly minimum version is and set up the orderly namespace for the appropriate version. } -\author{ -Richard Fitzjohn -}