Skip to content

Commit 044209f

Browse files
authored
Merge pull request #74 from r-lib/f-force-relative
- `has_file()` and `has_dir()` throw an error if the `filepath` argument is an absolute path (#74).
2 parents e8e2b55 + 57ca629 commit 044209f

File tree

2 files changed

+20
-3
lines changed

2 files changed

+20
-3
lines changed

R/root.R

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -183,6 +183,8 @@ has_file <- function(filepath, contents = NULL, n = -1L) {
183183
force(n)
184184
stopifnot(length(n) == 1)
185185

186+
check_relative(filepath)
187+
186188
testfun <- eval(bquote(function(path) {
187189
testfile <- file.path(path, .(filepath))
188190
if (!file.exists(testfile)) {
@@ -217,6 +219,8 @@ has_dir <- function(filepath) {
217219
force(filepath)
218220
stopifnot(is.character(filepath), length(filepath) == 1)
219221

222+
check_relative(filepath)
223+
220224
testfun <- eval(bquote(function(path) {
221225
testfile <- file.path(path, .(filepath))
222226
dir.exists(testfile)
@@ -227,6 +231,12 @@ has_dir <- function(filepath) {
227231
root_criterion(testfun, desc)
228232
}
229233

234+
check_relative <- function(filepath) {
235+
if (is_absolute_path(filepath)) {
236+
stop("filepath must be a file or a relative path, not an absolute path.", call. = FALSE)
237+
}
238+
}
239+
230240
#' @details
231241
#' The `has_file_pattern()` function constructs a criterion that checks for the
232242
#' existence of a file that matches a pattern, with specific contents.

tests/testthat/test-root.R

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,9 @@ test_that("has_file", {
7676
expect_error(
7777
find_root(has_file("e", "f", 1), path = path),
7878
"No root directory found.* file `.*` with contents .* in the first line"
79-
)
79+
),
80+
expect_error(has_file("/a"), "absolute"),
81+
TRUE
8082
)
8183
})
8284

@@ -120,7 +122,8 @@ test_that("has_file_pattern", {
120122
expect_error(
121123
find_root(has_file_pattern(glob2rx("e"), "f", 1), path = path),
122124
"No root directory found.* with contents .* in the first line"
123-
)
125+
),
126+
TRUE
124127
)
125128
})
126129

@@ -146,6 +149,7 @@ test_that("has_dir", {
146149
find_root(has_dir("rprojroot.Rproj"), path = path),
147150
"No root directory found.* a directory `.*`"
148151
),
152+
expect_error(has_dir("/a"), "absolute"),
149153
TRUE
150154
)
151155
})
@@ -291,7 +295,10 @@ test_that("is_git_root for separated git directory", {
291295
test_that("finds root", {
292296
skip_on_cran()
293297
# Checks that search for root actually terminates
294-
expect_error(find_root("/"), "No root directory found.* file `.*`")
298+
expect_error(
299+
find_root("9259cfa7884bf51eb9dd80b52c26dcdf9cd28e82"),
300+
"No root directory found.* file `.*`"
301+
)
295302
})
296303

297304
test_that("stops if depth reached", {

0 commit comments

Comments
 (0)