Skip to content

Commit

Permalink
keep RemoteSha if it appears to be a hash
Browse files Browse the repository at this point in the history
  • Loading branch information
kevinushey committed Aug 6, 2024
1 parent 8573b0d commit 91e9553
Show file tree
Hide file tree
Showing 2 changed files with 67 additions and 12 deletions.
38 changes: 26 additions & 12 deletions R/snapshot.R
Original file line number Diff line number Diff line change
Expand Up @@ -756,28 +756,42 @@ renv_snapshot_description_impl <- function(dcf, path = NULL) {
dcf[["Requirements"]] <- all

# get remotes fields
git <- grep("^git", names(dcf), value = TRUE)
remotes <- grep("^Remote", names(dcf), value = TRUE)

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

# drop remote metadata for 'standard' remotes, to avoid spurious
# diffs that could arise from installing a package using 'pak'
# versus 'install.packages()' or an alternate tool
std <- identical(dcf[["RemoteType"]], "standard")
remotes <- renv_snapshot_description_impl_remotes(dcf)

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

# 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)

}

renv_snapshot_description_source_custom <- function(dcf) {

# only proceed for cranlike remotes
Expand Down
41 changes: 41 additions & 0 deletions tests/testthat/test-snapshot.R
Original file line number Diff line number Diff line change
Expand Up @@ -573,3 +573,44 @@ test_that("packages installed from r-universe preserve remote metadata", {
expect_identical(record[["RemoteSha"]], "e4aafb92b86ba7eba3b7036d9d96fdfb6c32761a")

})

test_that("standard remotes preserve RemoteSha if it's a hash", {

text <- heredoc("
Package: skeleton
Type: Package
Version: 1.1.0
Remotes: kevinushey/skeleton
Repository: https://kevinushey.r-universe.dev
RemoteType: standard
RemoteUrl: https://github.com/kevinushey/skeleton
RemoteSha: e4aafb92b86ba7eba3b7036d9d96fdfb6c32761a
")

path <- renv_scope_tempfile()
writeLines(text, con = path)

record <- renv_snapshot_description(path = path)
expect_identical(record[["RemoteSha"]], "e4aafb92b86ba7eba3b7036d9d96fdfb6c32761a")

})

test_that("standard remotes drop RemoteSha if it's a version", {

text <- heredoc("
Package: skeleton
Type: Package
Version: 1.1.0
Remotes: kevinushey/skeleton
Repository: https://kevinushey.r-universe.dev
RemoteType: standard
RemoteSha: 1.1.0
")

path <- renv_scope_tempfile()
writeLines(text, con = path)

record <- renv_snapshot_description(path = path)
expect_null(record[["RemoteSha"]])

})

0 comments on commit 91e9553

Please sign in to comment.