Skip to content

Commit

Permalink
Merge pull request #489 from r2evans/feature/extlib_no_package
Browse files Browse the repository at this point in the history
change with_extlib to work without packages
  • Loading branch information
kevinushey authored Sep 17, 2018
2 parents eaf4435 + e3a76c3 commit cea6c23
Show file tree
Hide file tree
Showing 4 changed files with 62 additions and 8 deletions.
5 changes: 5 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
# Packrat 0.5.0 (UNRELEASED)

- `packrat::with_extlib()` now works with no `packages` provided;
both with and without this option, the new behavior is that `expr`
is executed in an environment where the original (not packrat)
library search path is in place.

- A project is now only considered 'packified' if it has both a Packrat
lockfile as well as the associated autoloader in the project `.Rprofile`.

Expand Down
24 changes: 19 additions & 5 deletions R/external.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,23 +5,34 @@
##' libraries; that is, the libraries that would be available upon launching a new
##' \R session.
##'
##' @param packages A set of package names (as a character vector) to load for
##' the duration of evaluation of \code{expr}.
##' @param packages An optional set of package names (as a character
##' vector) to load for the duration of evaluation of \code{expr}.
##' Whether \code{packages} is provided or \code{NULL} (the
##' default), \code{expr} is evaluated in an environment where the
##' external library path is in place, not the local (packrat)
##' library path.
##' @param expr An \R expression.
##' @param envir An environment in which the expression is evaluated.
##' @name packrat-external
##' @rdname packrat-external
##' @examples \dontrun{
##' with_extlib("lattice", xyplot(1 ~ 1))
##' with_extlib(expr = packageVersion("lattice"))
##' # since devtools requires roxygen2 >= 5.0.0 for this step, this
##' # should fail unless roxygen2 is available in the packrat lib.loc
##' with_extlib("devtools", load_all("path/to/project"))
##' # this method will work given roxygen2 is installed in the
##' # non-packrat lib.loc with devtools
##' with_extlib(expr = devtools::load_all("path/to/project"))
##' }
##' @export
with_extlib <- function(packages, expr, envir = parent.frame()) {
with_extlib <- function(packages = NULL, expr, envir = parent.frame()) {

# need to force this promise now otherwise it will get evaluated
# in the wrong context later on
force(envir)

if (!is.character(packages)) {
if (!is.null(packages) && !is.character(packages)) {
stop("'packages' should be a character vector of libraries", call. = FALSE)
}

Expand All @@ -34,11 +45,13 @@ with_extlib <- function(packages, expr, envir = parent.frame()) {
oldSearch <- search()

libPaths <- .packrat_mutables$get("origLibPaths")
oldLibPaths <- .libPaths()
if (!length(libPaths))
libPaths <- getDefaultLibPaths()
.libPaths(libPaths)

for (package in packages) {
library(package, character.only = TRUE, lib.loc = libPaths, warn.conflicts = FALSE)
library(package, character.only = TRUE, warn.conflicts = FALSE)
}

## Evaluate the call
Expand All @@ -57,6 +70,7 @@ with_extlib <- function(packages, expr, envir = parent.frame()) {
for (path in setdiff(newSearch, oldSearch)) {
try(forceUnload(path))
}
.libPaths(oldLibPaths)
})

})
Expand Down
17 changes: 14 additions & 3 deletions man/packrat-external.Rd

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

24 changes: 24 additions & 0 deletions tests/testthat/test-with_extlib.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
context("extlib without packages")

test_that("with_extlib successfully works with no packages provided", {

## Make sure packrat mode is off
if (packrat:::isPackratModeOn())
packrat::off()

orig_libs <- packrat:::getLibPaths()
.libPaths(c(file.path(getwd(), "packages"), orig_libs))
on.exit(.libPaths(orig_libs), add = TRUE)

expect_identical(packageVersion("bread"), package_version("1.0.0"))

# don't use packrat::on so we can avoid the initialization step
packrat:::setPackratModeOn(auto.snapshot = FALSE, clean.search.path = FALSE)

expect_error(packageVersion("bread"), "package 'bread' not found")

expect_identical(packrat::with_extlib(expr = packageVersion("bread")), package_version("1.0.0"))

packrat::off()

})

0 comments on commit cea6c23

Please sign in to comment.