Skip to content

Commit

Permalink
add retrieve function, for downloading packages (#1968)
Browse files Browse the repository at this point in the history
* add retrieve API

* add some more tests

* add examples

* add to pkgdown

* respect destdir when copying from cache

* skip cache when using destdir

* document destdir caveat

* documentation

* re-run CI
  • Loading branch information
kevinushey authored Aug 15, 2024
1 parent 163757b commit 4e10013
Show file tree
Hide file tree
Showing 14 changed files with 225 additions and 35 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ export(rehash)
export(remove)
export(repair)
export(restore)
export(retrieve)
export(revert)
export(run)
export(sandbox)
Expand Down
5 changes: 5 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,11 @@

# renv (development version)

* `renv` gains the function `renv::retrieve()`, which can be used to download
packages without installing them. This is primarily useful in CI / CD scenarios,
where you might want to download packages in a single stage before attempting
to install / restore them. (#1965)

* `renv` now preserves `Remote` fields present on packages installed from
public package repositories (e.g. <https://r-universe.dev/>). (#1961)

Expand Down
2 changes: 1 addition & 1 deletion R/hydrate.R
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,7 @@ renv_hydrate_resolve_missing <- function(project, library, remotes, missing) {
handler = handler
)

records <- retrieve(packages)
records <- renv_retrieve_impl(packages)
renv_install_impl(records)

# if we failed to restore anything, warn the user
Expand Down
2 changes: 1 addition & 1 deletion R/imbue.R
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ renv_imbue_impl <- function(project,
recursive = FALSE
)

records <- retrieve("renv")
records <- renv_retrieve_impl("renv")
renv_install_impl(records)

record <- records[["renv"]]
Expand Down
20 changes: 1 addition & 19 deletions R/install.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,24 +43,6 @@ the$install_step_width <- 48L
#'
#' @inherit renv-params
#'
#' @param packages Either `NULL` (the default) to install all packages required
#' by the project, or a character vector of packages to install. renv
#' supports a subset of the remotes syntax used for package installation,
#' e.g:
#'
#' * `pkg`: install latest version of `pkg` from CRAN.
#' * `pkg@version`: install specified version of `pkg` from CRAN.
#' * `username/repo`: install package from GitHub
#' * `bioc::pkg`: install `pkg` from Bioconductor.
#'
#' See <https://remotes.r-lib.org/articles/dependencies.html> and the examples
#' below for more details.
#'
#' renv deviates from the remotes spec in one important way: subdirectories
#' are separated from the main repository specification with a `:`, not `/`.
#' So to install from the `subdir` subdirectory of GitHub package
#' `username/repo` you'd use `"username/repo:subdir`.
#'
#' @param exclude Packages which should not be installed. `exclude` is useful
#' when using `renv::install()` to install all dependencies in a project,
#' except for a specific set of packages.
Expand Down Expand Up @@ -224,7 +206,7 @@ install <- function(packages = NULL,
)

# retrieve packages
records <- retrieve(packages)
records <- renv_retrieve_impl(packages)
if (empty(records)) {
writef("- There are no packages to install.")
return(invisible(list()))
Expand Down
1 change: 1 addition & 0 deletions R/remotes.R
Original file line number Diff line number Diff line change
Expand Up @@ -451,6 +451,7 @@ renv_remotes_resolve_repository <- function(remote, latest) {
if (latest && is.null(version)) {
remote <- renv_available_packages_latest(package)
version <- remote$Version
repository <- remote$Repository
}

list(
Expand Down
2 changes: 1 addition & 1 deletion R/restore.R
Original file line number Diff line number Diff line change
Expand Up @@ -212,7 +212,7 @@ renv_restore_run_actions <- function(project, actions, current, lockfile, rebuil
packages <- names(installs)

# perform the install
records <- retrieve(packages)
records <- renv_retrieve_impl(packages)
renv_install_impl(records)

# detect dependency tree repair
Expand Down
108 changes: 99 additions & 9 deletions R/retrieve.R
Original file line number Diff line number Diff line change
@@ -1,10 +1,95 @@

the$repos_archive <- new.env(parent = emptyenv())

# this routine retrieves a package + its dependencies, and as a side
# effect populates the restore state's `retrieved` member with a
# list of package records which can later be used for install
retrieve <- function(packages) {
#' Retrieve packages
#'
#' Retrieve (download) one or more packages from external sources.
#' Using `renv::retrieve()` can be useful in CI / CD workflows, where
#' you might want to download all packages listed in a lockfile
#' before later invoking [renv::restore()]. Packages will be downloaded
#' to an internal path within `renv`'s local state directories -- see
#' [paths] for more details.
#'
#' If `destdir` is `NULL` and the requested package is already available
#' within the `renv` cache, `renv` will return the path to that package
#' directory in the cache.
#'
#' @inheritParams renv-params
#'
#' @param lockfile The path to an `renv` lockfile. When set, `renv`
#' will retrieve the packages as defined within that lockfile.
#' If `packages` is also non-`NULL`, then only those packages will
#' be retrieved.
#'
#' @param destdir The directory where packages should be downloaded.
#' When `NULL` (the default), the default internal storage locations
#' (normally used by e.g. [renv::install()] or [renv::restore()]) will
#' be used.
#'
#' @returns A named vector, mapping package names to the paths where
#' those packages were downloaded.
#'
#' @export
#'
#' @examples
#' \dontrun{
#'
#' # retrieve package + versions as defined in the lockfile
#' # normally used as a pre-flight step to renv::restore()
#' renv::retrieve()
#'
#' # download one or more packages locally
#' renv::retrieve("rlang", destdir = ".")
#'
#' }
retrieve <- function(packages = NULL,
...,
lockfile = NULL,
destdir = NULL,
project = NULL)
{
renv_consent_check()
renv_scope_error_handler()
renv_dots_check(...)

project <- renv_project_resolve(project)
renv_project_lock(project = project)

# set destdir if available
if (!is.null(destdir)) {
renv_scope_options(renv.config.cache.enabled = FALSE)
renv_scope_binding(the, "destdir", destdir)
}

# figure out which records we want to retrieve
if (is.null(packages) && is.null(lockfile)) {
lockfile <- renv_lockfile_load(project = project)
} else if (is.null(lockfile)) {
records <- map(packages, renv_remotes_resolve, latest = TRUE)
packages <- map_chr(records, `[[`, "Package")
names(records) <- packages
} else if (is.character(lockfile)) {
lockfile <- renv_lockfile_read(lockfile)
records <- renv_lockfile_records(lockfile)
packages <- packages %||% names(records)
}

# overlay project remotes
records <- overlay(renv_project_remotes(project), records)

# perform the retrieval
renv_scope_restore(
project = project,
library = library,
packages = packages,
records = records
)

result <- renv_retrieve_impl(packages)
map_chr(result, `[[`, "Path")
}

renv_retrieve_impl <- function(packages) {

# confirm that we have restore state set up
state <- renv_restore_state()
Expand All @@ -31,7 +116,7 @@ retrieve <- function(packages) {
before <- Sys.time()
handler <- state$handler
for (package in packages)
handler(package, renv_retrieve_impl(package))
handler(package, renv_retrieve_impl_one(package))
after <- Sys.time()

state <- renv_restore_state()
Expand All @@ -46,7 +131,7 @@ retrieve <- function(packages) {

}

renv_retrieve_impl <- function(package) {
renv_retrieve_impl_one <- function(package) {

# skip packages with 'base' priority
if (package %in% renv_packages_base())
Expand Down Expand Up @@ -169,6 +254,7 @@ renv_retrieve_impl <- function(package) {
path <- renv_cache_find(record)
if (nzchar(path) && renv_cache_package_validate(path))
return(renv_retrieve_successful(record, path))

}

}
Expand Down Expand Up @@ -251,10 +337,14 @@ renv_retrieve_path <- function(record, type = "source", ext = NULL) {
# extract relevant record information
package <- record$Package
name <- renv_retrieve_name(record, type, ext)
source <- renv_record_source(record)

# if we have a destdir override, use this
if (!is.null(the$destdir))
return(file.path(the$destdir, name))

# check for packages from an PPM binary URL, and
# update the package type if known
source <- renv_record_source(record)
if (renv_ppm_enabled()) {
url <- attr(record, "url")
if (is.character(url) && grepl("/__[^_]+__/", url))
Expand Down Expand Up @@ -1139,14 +1229,14 @@ renv_retrieve_successful_recurse_impl_one <- function(remote) {

# if this is a 'plain' package remote, retrieve it
if (grepl(renv_regexps_package_name(), remote)) {
renv_retrieve_impl(remote)
renv_retrieve_impl_one(remote)
return(list())
}

# otherwise, handle custom remotes
record <- renv_retrieve_remotes_impl(remote)
if (length(record)) {
renv_retrieve_impl(record$Package)
renv_retrieve_impl_one(record$Package)
return(list())
}

Expand Down
18 changes: 18 additions & 0 deletions R/roxygen.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,24 @@
#' "strong", "most", and "all" are also supported.
#' See [tools::package_dependencies()] for more details.
#'
#' @param packages Either `NULL` (the default) to install all packages required
#' by the project, or a character vector of packages to install. renv
#' supports a subset of the remotes syntax used for package installation,
#' e.g:
#'
#' * `pkg`: install latest version of `pkg` from CRAN.
#' * `pkg@version`: install specified version of `pkg` from CRAN.
#' * `username/repo`: install package from GitHub
#' * `bioc::pkg`: install `pkg` from Bioconductor.
#'
#' See <https://remotes.r-lib.org/articles/dependencies.html> and the examples
#' below for more details.
#'
#' renv deviates from the remotes spec in one important way: subdirectories
#' are separated from the main repository specification with a `:`, not `/`.
#' So to install from the `subdir` subdirectory of GitHub package
#' `username/repo` you'd use `"username/repo:subdir`.
#'
#' @return The project directory, invisibly. Note that this function is normally
#' called for its side effects.
#'
Expand Down
2 changes: 1 addition & 1 deletion R/tests.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ renv_test_retrieve <- function(record) {
recursive = TRUE
)

records <- retrieve(record$Package)
records <- renv_retrieve_impl(record$Package)
renv_install_impl(records)

descpath <- file.path(templib, package)
Expand Down
2 changes: 1 addition & 1 deletion R/upgrade.R
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ renv_upgrade_impl <- function(project, version, reload, prompt) {
)

# retrieve and install renv
records <- retrieve("renv")
records <- renv_retrieve_impl("renv")
renv_install_impl(records)

# update the lockfile
Expand Down
5 changes: 3 additions & 2 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -71,10 +71,11 @@ reference:

- title: internal
contents:
- graph
- imbue
- renv-package
- retrieve
- sandbox
- imbue
- graph
- sandbox

articles:
Expand Down
74 changes: 74 additions & 0 deletions man/retrieve.Rd

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

Loading

0 comments on commit 4e10013

Please sign in to comment.