Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

include all required fields for hashing in lockfile #2059

Open
wants to merge 18 commits into
base: main
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from 6 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
61 changes: 41 additions & 20 deletions R/hash.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,44 @@ renv_hash_text <- function(text) {
renv_bootstrap_hash_text(text)
}

renv_hash_fields <- function(dcf) {
c(
renv_hash_fields_default(),
renv_hash_fields_remotes(dcf)
)
}

renv_hash_fields_default <- function() {
c(
"Package", "Version", "Title",
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Title, Authors, Maintainer, and Description are not necessary for hashing, as they do not communicate anything about package dependencies.

What about SystemRequirements and NeedsCompilation?

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

FWIW if we change the fields that get included in the hash, then we'll invalidate any old hash values. We could still do this, but we'd probably want to do something to either notify users or allow them to choose.

Ultimately though, we want to include fields which would help to uniquely identify a package from its DESCRIPTION file, hence why those (and not just the package dependency fields) are included.

"Author", "Maintainer", "Description",
"Depends", "Imports", "Suggests", "LinkingTo"
)
}

renv_hash_fields_remotes <- function(dcf) {

# if this seems to be a cran-like record, only keep remotes
# when RemoteSha appears to be a hash (e.g. for r-universe)
# note that RemoteSha may be a package version when installed
# by e.g. pak
if (renv_record_cranlike(dcf)) {
sha <- dcf[["RemoteSha"]]
if (is.null(sha) || nchar(sha) < 40L)
return(character())
}

# grab the relevant remotes
remotes <- grep("^Remote", names(dcf), perl = TRUE, value = TRUE)

# don't include 'RemoteRef' if it's a non-informative remote
if (identical(dcf[["RemoteRef"]], "HEAD"))
remotes <- setdiff(remotes, "RemoteRef")

remotes

}

renv_hash_description <- function(path) {
filebacked(
context = "renv_hash_description",
Expand All @@ -19,17 +57,11 @@ renv_hash_description_impl <- function(path) {
~ stop("unexpected path '%s'", path)
)

# include default fields
fields <- c(
"Package", "Version", "Title", "Author", "Maintainer", "Description",
"Depends", "Imports", "Suggests", "LinkingTo"
)

# add remotes fields
remotes <- renv_hash_description_remotes(dcf)
# find relevant fields for hashing
fields <- renv_hash_fields(dcf)

# retrieve these fields
subsetted <- dcf[renv_vector_intersect(c(fields, remotes), names(dcf))]
subsetted <- dcf[renv_vector_intersect(fields, names(dcf))]

# sort names (use C locale to ensure consistent ordering)
ordered <- subsetted[csort(names(subsetted))]
Expand Down Expand Up @@ -71,14 +103,3 @@ renv_hash_description_impl <- function(path) {
invisible(hash)

}

renv_hash_description_remotes <- function(dcf) {

# ignore other remote fields for cranlike remotes
if (renv_record_cranlike(dcf))
return(character())

# otherwise, include any other discovered remote fields
grep("^Remote", names(dcf), value = TRUE)

}
4 changes: 1 addition & 3 deletions R/lockfile-write.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,9 +90,7 @@ renv_lockfile_write_json <- function(lockfile, file = stdout()) {

prepared <- enumerate(lockfile, renv_lockfile_write_json_prepare)

box <- c("Depends", "Imports", "Suggests", "LinkingTo", "Requirements")
config <- list(box = box)
json <- renv_json_convert(prepared, config)
json <- renv_json_convert(prepared)
if (is.null(file))
return(json)

Expand Down
1 change: 1 addition & 0 deletions R/lockfile.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,7 @@ renv_lockfile_save <- function(lockfile, project) {
}

renv_lockfile_load <- function(project, strict = FALSE) {

path <- renv_lockfile_path(project)
if (file.exists(path))
return(renv_lockfile_read(path))
Expand Down
2 changes: 1 addition & 1 deletion R/record.R
Original file line number Diff line number Diff line change
Expand Up @@ -121,5 +121,5 @@ renv_record_placeholder <- function() {

renv_record_cranlike <- function(record) {
type <- record[["RemoteType"]]
is.null(type) || type %in% c("cran", "repository", "standard")
is.null(type) || tolower(type) %in% c("cran", "repository", "standard")
}
66 changes: 25 additions & 41 deletions R/snapshot.R
Original file line number Diff line number Diff line change
Expand Up @@ -741,54 +741,38 @@ renv_snapshot_description_impl <- function(dcf, path = NULL) {
dcf <- dcf[fields]
}

# drop fields that normally only appear in binary packages,
# or fields which might differ from user to user, or might
# differ depending on the mirror used for publication
ignore <- c("Archs", "Built", "Date/Publication", "File", "MD5sum", "Packaged")
dcf[ignore] <- NULL

# drop remote fields for cranlike remotes
if (renv_record_cranlike(dcf)) {
sha <- dcf[["RemoteSha"]]
if (is.null(sha) || nchar(sha) < 40L) {
remotes <- grep("^Remote", names(dcf), perl = TRUE, value = TRUE)
dcf[remotes] <- NULL
}
}

# drop the old Github remote fields
github <- grepl("^Github", names(dcf), perl = TRUE)
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

aside: When RemoteType: github and RemoteHost: api.github.com, each of the remote Repo, Username, Ref, and Sha fields can be transformed into the Github equivalents (Sha becoming SHA1).

dcf <- dcf[!github]

# generate a hash if we can
dcf[["Hash"]] <- if (the$auto_snapshot_hash) {
if (is.null(path))
renv_hash_description_impl(dcf)
else
renv_hash_description(path)
}

# generate a Requirements field -- primarily for use by 'pak'
fields <- c("Depends", "Imports", "LinkingTo")
deps <- bind(map(dcf[fields], renv_description_parse_field))
all <- unique(csort(unlist(deps$Package)))
dcf[["Requirements"]] <- all

# get remotes fields
remotes <- renv_snapshot_description_impl_remotes(dcf)

# only keep relevant fields
extra <- c("Repository", "OS_type")
all <- c(required, extra, remotes, "Requirements", "Hash")
keep <- renv_vector_intersect(all, names(dcf))


# reorganize fields a bit
dcf <- dcf[c(required, setdiff(names(dcf), required))]

# return as list
as.list(dcf[keep])

}

renv_snapshot_description_impl_remotes <- function(dcf) {

# if this seems to be a cran-like record, only keep remotes
# when RemoteSha appears to be a hash (e.g. for r-universe)
# note that RemoteSha may be a package version when installed
# by e.g. pak
if (renv_record_cranlike(dcf)) {
sha <- dcf[["RemoteSha"]]
if (is.null(sha) || nchar(sha) < 40)
return(character())
}

# grab the relevant remotes
git <- grep("^git", names(dcf), value = TRUE)
remotes <- grep("^Remote(?!s)", names(dcf), perl = TRUE, value = TRUE)

# don't include 'RemoteRef' if it's a non-informative remote
if (identical(dcf[["RemoteRef"]], "HEAD"))
remotes <- setdiff(remotes, "RemoteRef")

c(git, remotes)
as.list(dcf)

}

Expand Down Expand Up @@ -840,7 +824,7 @@ renv_snapshot_description_source <- function(dcf) {

# check for a custom declared remote type
if (!renv_record_cranlike(dcf)) {
type <- dcf[["RemoteType"]]
type <- dcf[["RemoteType"]] %||% "standard"
return(list(Source = alias(type)))
}

Expand Down
2 changes: 1 addition & 1 deletion R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
}

# don't lock sandbox while testing / checking
options(renv.sandbox.locking_enabled = FALSE)
Sys.setenv(RENV_SANDBOX_LOCKING_ENABLED = FALSE)

}

Expand Down
6 changes: 2 additions & 4 deletions tests/testthat/test-bioconductor.R
Original file line number Diff line number Diff line change
Expand Up @@ -222,11 +222,9 @@ test_that("standard bioc remotes are standardized appropriately", {
Package = "BiocVersion",
Version = "3.18.1",
Source = "Bioconductor",
Repository = "Bioconductor 3.18",
Requirements = "R",
Hash = "2ecaed86684f5fae76ed5530f9d29c4a"
Repository = "Bioconductor 3.18"
)

expect_identical(actual, expected)
expect_identical(actual[names(expected)], expected)

})
21 changes: 11 additions & 10 deletions tests/testthat/test-lockfile.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,22 +53,23 @@ test_that("we create lockfile from a manifest automatically when no lockfile fou

skip_on_cran()

project_dir <- tempfile()
dir.create(project_dir)
project <- tempfile()
dir.create(project)

manifest <- "resources/manifest.json"
expected_lock <- renv_lockfile_from_manifest("resources/manifest.json")
file.copy(manifest, file.path(project_dir, "manifest.json"))
path <- renv_tests_path("resources/manifest.json")
expected <- renv_lockfile_from_manifest(path)
file.copy(path, file.path(project, "manifest.json"))

# when called with `strict = TRUE` does not create manifest
expect_error(renv_lockfile_load(project_dir, strict = TRUE))
expect_error(renv_lockfile_load(project, strict = TRUE))

# creates and reads lockfile
obtained_lock <- renv_lockfile_load(project_dir)
expect_identical(expected_lock, obtained_lock)
expect_true(file.exists(file.path(project_dir, "renv.lock")))
actual <- renv_lockfile_load(project)
expect_identical(expected, actual)
expect_true(file.exists(file.path(project, "renv.lock")))

unlink(project_dir, recursive = TRUE)
unlink(project, recursive = TRUE)

})

test_that("the Requirements field is read as character", {
Expand Down
24 changes: 19 additions & 5 deletions tests/testthat/test-snapshot.R
Original file line number Diff line number Diff line change
Expand Up @@ -397,13 +397,11 @@ test_that("packages installed from CRAN using pak are handled", {
library <- renv_paths_library()
ensure_directory(library)
pak <- renv_namespace_load("pak")
suppressMessages(pak$pkg_install("toast"))
quietly(pak$pkg_install("toast"))
record <- renv_snapshot_description(package = "toast")

expect_named(
record,
c("Package", "Version", "Source", "Repository", "Requirements", "Hash")
)
expected <- c("Package", "Version", "Source", "Repository", "Hash")
expect_contains(names(record), expected)

expect_identical(record$Source, "Repository")
expect_identical(record$Repository, "CRAN")
Expand Down Expand Up @@ -615,3 +613,19 @@ test_that("standard remotes drop RemoteSha if it's a version", {
expect_null(record[["RemoteSha"]])

})

test_that("a package's hash can be re-generated from lockfile", {

project <- renv_tests_scope("breakfast")
init()

lockfile <- snapshot(lockfile = NULL)
records <- renv_lockfile_records(lockfile)

map(records, function(record) {
actual <- record[["Hash"]]
expected <- renv_hash_description_impl(record)
expect_equal(actual, expected)
})

})
4 changes: 0 additions & 4 deletions tests/testthat/test-vendor.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,10 +43,6 @@ test_that("renv can be vendored into an R package", {
base <- .BaseNamespaceEnv
base$.libPaths(path)

# extra sanity check
if (requireNamespace("renv", quietly = TRUE))
stop("internal error: renv shouldn't be visible on library paths")

# load the package, and check that renv realizes it's embedded
namespace <- base$asNamespace("test.renv.embedding")
embedded <- namespace$renv$renv_metadata_embedded()
Expand Down
Loading