Skip to content

Commit

Permalink
Scan deps: add root argument (#433)
Browse files Browse the repository at this point in the history
  • Loading branch information
gaborcsardi authored Jan 8, 2025
1 parent 99fe52c commit 59abf4e
Show file tree
Hide file tree
Showing 6 changed files with 116 additions and 6 deletions.
42 changes: 38 additions & 4 deletions R/scan-deps.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,20 @@
#' * Test dependencies: `"test"`.
#' * Development dependencies: `"dev"`.
#'
#' @param path Path to the directory of the project.
#' @param path Files and/or directories to scan. Directories
#' are scanned recursively. If you list files or folders from multiple
#' projects, then you need to specify `root` explicitly.
#' @param root The root directory of the project. It is used to find the
#' `.gitignore` and `.renvignore` files. Set it to `NA` if the files do
#' not belong to any project or you want to ignore the project
#' configuration. By default it is detected automatically by finding the
#' first parent directory that contains a file or directory called
#' `r cli::format_inline("{.or {pkgdepends:::project_root_anchors}}")`,
#' for each path in `path`. If the automatic detection does not work,
#' and `path` is a single directory, then `path` is used as `root`.
#' Otherwise, if the automatic detection fails or detects different
#' projects for different paths, an error is thrown, and the user will
#' need to provide `root` explicitly.
#' @return Data frame with columns:
#' * `path`: Path to the file in which the dependencies was found.
#' * `package`: Detected package dependency. Typically a package name,
Expand All @@ -81,13 +94,14 @@
#'
#' @export

scan_deps <- function(path = ".") {
path <- tryCatch(find_project_root(path), error = function(...) path)
scan_deps <- function(path = ".", root = NULL) {
path <- normalizePath(path, winslash = "/")
root <- root %||% find_common_root(path)
paths <- c(
dir(path, pattern = scan_deps_pattern(), recursive = TRUE),
dir(path, pattern = scan_deps_pattern_root(), recursive = FALSE)
)
full_paths <- normalizePath(file.path(path, paths))
full_paths <- normalizePath(file.path(path, paths), winslash = "/")
deps_list <- lapply(full_paths, scan_path_deps)
deps <- do.call("rbind", c(list(scan_deps_df()), deps_list))
# write back the relative paths
Expand All @@ -97,6 +111,26 @@ scan_deps <- function(path = ".") {
deps
}

find_common_root <- function(paths) {
paths <- normalizePath(paths, winslash = "/", mustWork = TRUE)
roots <- vcapply(paths, USE.NAMES = FALSE, function(path) {
tryCatch(find_project_root(path), error = function(e) NA_character_)
})
if (length(paths) == 1) {
if (!is.na(roots)) {
roots
} else {
paths
}
} else {
uroot <- unique(roots)
if (anyNA(roots) || length(uroot) > 1) {
stop("Cannot find common project root directory for paths")
}
uroot
}
}

scan_deps_pattern <- function() {
ptrns <- c(
"[.]R$",
Expand Down
2 changes: 2 additions & 0 deletions inst/WORDLIST
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ PBC
RSPM
RStudio
RedHat
Rproj
SHA
Shorthands
Sur
Expand Down Expand Up @@ -44,6 +45,7 @@ pkgdown
prerelease
prettyunits
ragg
renv
rpart
rprojroot
rstanarm
Expand Down
18 changes: 16 additions & 2 deletions man/scan_deps.Rd

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

8 changes: 8 additions & 0 deletions tests/testthat/_snaps/scan-deps.md
Original file line number Diff line number Diff line change
Expand Up @@ -512,3 +512,11 @@
3 notebook.ipynb stats stats * prod stats::setNames 1 1 1
4 notebook.ipynb cli cli * prod cli::cli_text 2 1 19

# find_common_root

Code
find_common_root(c("d2/sd1", "d2/sd2"))
Condition
Error:
! Cannot find common project root directory for paths

7 changes: 7 additions & 0 deletions tests/testthat/helper.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,13 @@ test_temp_dir <- function(pattern = "test-dir-", envir = parent.frame()) {
normalizePath(tmp)
}

# Create a temporary directory and switch the working directory to it
local_temp_dir <- function(..., .local_envir = parent.frame()) {
tmp <- withr::local_tempdir(..., .local_envir = .local_envir)
withr::local_dir(tmp, .local_envir = .local_envir)
invisible(tmp)
}

test_package_root <- function() {
x <- tryCatch(
find_package_root(),
Expand Down
45 changes: 45 additions & 0 deletions tests/testthat/test-scan-deps.R
Original file line number Diff line number Diff line change
Expand Up @@ -553,3 +553,48 @@ test_that("IPython notebook", {
scan_path_deps_do(readLines(path), basename(path))
})
})

test_that("find_common_root", {
local_temp_dir()

# simple, common case
mkdirp("foo")
file.create("foo/DESCRIPTION")
expect_equal(
find_common_root("foo"),
normalizePath("foo", winslash = "/")
)

# common root
mkdirp("d1")
file.create("d1/renv.lock")
mkdirp("d1/sd1")
mkdirp("d1/sd2/ssd1")
expect_equal(
find_common_root(c("d1/sd1", "d1/sd2/ssd1")),
normalizePath("d1", winslash = "/")
)

# no project, single path
mkdirp("bar")
fake(find_common_root, "find_project_root", function(...) stop("no"))
expect_equal(
find_common_root("bar"),
normalizePath("bar", winslash = "/")
)

# no project for one path
mkdirp("d2/sd1")
file.create("d2/sd1/DESCRIPTION")
mkdirp("d2/sd2")
fake(find_common_root, "find_project_root", function(path) {
if (path == normalizePath("d2/sd1")) {
find_project_root(path)
} else {
stop("no")
}
})
expect_snapshot(error = TRUE, {
find_common_root(c("d2/sd1", "d2/sd2"))
})
})

0 comments on commit 59abf4e

Please sign in to comment.