Skip to content

Commit 0e3eb9d

Browse files
file path detection in paste_linter (#2074)
1 parent 781a18d commit 0e3eb9d

File tree

6 files changed

+229
-4
lines changed

6 files changed

+229
-4
lines changed

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@
2323
+ `yoda_test_linter()`
2424
* `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico).
2525
* `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico).
26+
* `paste_linter()` gains detection for file paths that are better constructed with `file.path()`, e.g. `paste0(dir, "/", file)` would be better as `file.path(dir, file)` (part of #884, @MichaelChirico).
2627

2728
### New linters
2829

R/methods.R

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,7 @@ markdown <- function(x, info, ...) {
4545
as.character(x$line_number), ":",
4646
as.character(x$column_number), ":", "]",
4747
"(",
48-
paste(
49-
sep = "/",
48+
file.path(
5049
"https://github.com",
5150
info$user,
5251
info$repo,

R/paste_linter.R

Lines changed: 103 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@
2121
#' `paste()` with `sep = ""` is not linted.
2222
#' @param allow_to_string Logical, default `FALSE`. If `TRUE`, usage of
2323
#' `paste()` and `paste0()` with `collapse = ", "` is not linted.
24+
#' @param allow_file_path Logical, default `FALSE`. If `TRUE`, usage of
25+
#' `paste()` and `paste0()` to construct file paths is not linted.
2426
#'
2527
#' @examples
2628
#' # will produce lints
@@ -44,6 +46,11 @@
4446
#' linters = paste_linter()
4547
#' )
4648
#'
49+
#' lint(
50+
#' text = 'paste0(dir, "/", file)',
51+
#' linters = paste_linter()
52+
#' )
53+
#'
4754
#' # okay
4855
#' lint(
4956
#' text = 'paste0("a", "b")',
@@ -75,9 +82,14 @@
7582
#' linters = paste_linter()
7683
#' )
7784
#'
85+
#' lint(
86+
#' text = 'paste0(year, "/", month, "/", day)',
87+
#' linters = paste_linter(allow_file_path = TRUE)
88+
#' )
89+
#'
7890
#' @seealso [linters] for a complete list of linters available in lintr.
7991
#' @export
80-
paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
92+
paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE, allow_file_path = FALSE) {
8193
sep_xpath <- "
8294
//SYMBOL_FUNCTION_CALL[text() = 'paste']
8395
/parent::expr
@@ -111,6 +123,70 @@ paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
111123
/parent::expr
112124
"
113125

126+
slash_str <- sprintf("STR_CONST[%s]", xp_text_in_table(c("'/'", '"/"')))
127+
str_not_start_with_slash <-
128+
"STR_CONST[not(substring(text(), 2, 1) = '/')]"
129+
str_not_end_with_slash <-
130+
"STR_CONST[not(substring(text(), string-length(text()) - 1, 1) = '/')]"
131+
non_str <- "SYMBOL or expr"
132+
133+
# Type I: paste(..., sep = "/")
134+
paste_file_path_xpath <- glue("
135+
//SYMBOL_FUNCTION_CALL[text() = 'paste']
136+
/parent::expr
137+
/parent::expr[
138+
SYMBOL_SUB[text() = 'sep']/following-sibling::expr[1][{slash_str}]
139+
and not(SYMBOL_SUB[text() = 'collapse'])
140+
]
141+
")
142+
143+
# Type II: paste0(x, "/", y, "/", z)
144+
paste0_file_path_xpath <- xp_strip_comments(glue("
145+
//SYMBOL_FUNCTION_CALL[text() = 'paste0']
146+
/parent::expr
147+
/parent::expr[
148+
(: exclude paste0(x) :)
149+
count(expr) > 2
150+
(: An expression matching _any_ of these conditions is _not_ a file path :)
151+
and not(
152+
(: Any numeric input :)
153+
expr/NUM_CONST
154+
(: A call using collapse= :)
155+
or SYMBOL_SUB[text() = 'collapse']
156+
(: First input is '/', meaning file.path() would need to start with '' :)
157+
or expr[2][{slash_str}]
158+
(: Last input is '/', meaning file.path() would need to end with '' :)
159+
or expr[last()][{slash_str}]
160+
(: String starting or ending with multiple / :)
161+
(: TODO(#2075): run this logic on the actual R string :)
162+
or expr/STR_CONST[
163+
(: NB: this is (text, initial_index, n_characters) :)
164+
substring(text(), 2, 2) = '//'
165+
or substring(text(), string-length(text()) - 2, 2) = '//'
166+
]
167+
(: Consecutive non-strings like paste0(x, y) :)
168+
or expr[({non_str}) and following-sibling::expr[1][{non_str}]]
169+
(: A string not ending with /, followed by non-string or string not starting with / :)
170+
or expr[
171+
{str_not_end_with_slash}
172+
and following-sibling::expr[1][
173+
{non_str}
174+
or {str_not_start_with_slash}
175+
]
176+
]
177+
(: A string not starting with /, preceded by a non-string :)
178+
(: NB: consecutive strings is covered by the previous condition :)
179+
or expr[
180+
{str_not_start_with_slash}
181+
and preceding-sibling::expr[1][{non_str}]
182+
]
183+
)
184+
]
185+
"))
186+
187+
empty_paste_note <-
188+
'Note that paste() converts empty inputs to "", whereas file.path() leaves it empty.'
189+
114190
Linter(function(source_expression) {
115191
if (!is_lint_level(source_expression, "expression")) {
116192
return(list())
@@ -170,6 +246,32 @@ paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
170246
type = "warning"
171247
)
172248

249+
if (!allow_file_path) {
250+
paste_file_path_expr <- xml_find_all(xml, paste_file_path_xpath)
251+
optional_lints <- c(optional_lints, xml_nodes_to_lints(
252+
paste_file_path_expr,
253+
source_expression = source_expression,
254+
lint_message = paste(
255+
'Construct file paths with file.path(...) instead of paste(..., sep = "/").',
256+
'If you are using paste(sep = "/") to construct a date,',
257+
"consider using format() or lubridate helpers instead.",
258+
empty_paste_note
259+
),
260+
type = "warning"
261+
))
262+
263+
paste0_file_path_expr <- xml_find_all(xml, paste0_file_path_xpath)
264+
optional_lints <- c(optional_lints, xml_nodes_to_lints(
265+
paste0_file_path_expr,
266+
source_expression = source_expression,
267+
lint_message = paste(
268+
'Construct file paths with file.path(...) instead of paste0(x, "/", y, "/", z).',
269+
empty_paste_note
270+
),
271+
type = "warning"
272+
))
273+
}
274+
173275
c(optional_lints, paste0_sep_lints, paste_strrep_lints)
174276
})
175277
}

R/xp_utils.R

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -65,3 +65,17 @@ xp_find_location <- function(xml, xpath) {
6565
as.integer(xml_find_num(xml, xpath))
6666
}
6767
}
68+
69+
#' Strip XPath 2.0-style comments from an XPath
70+
#'
71+
#' xml2 uses XPath 1.0, which has no support for comments. But comments are
72+
#' useful in a codebase with as many XPaths as we maintain, so we fudge our
73+
#' way to XPath 2.0-ish support by writing this simple function to remove comments.
74+
#'
75+
#' @noRd
76+
xpath_comment_re <- rex::rex(
77+
"(:",
78+
zero_or_more(not(":)")),
79+
":)"
80+
)
81+
xp_strip_comments <- function(xpath) rex::re_substitutes(xpath, xpath_comment_re, "", global = TRUE)

man/paste_linter.Rd

Lines changed: 18 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-paste_linter.R

Lines changed: 92 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -113,3 +113,95 @@ test_that("paste_linter blocks simple disallowed usages", {
113113
expect_lint("paste0(rep('*', 20L), collapse='')", lint_msg, linter)
114114
expect_lint("paste(rep('#', width), collapse='')", lint_msg, linter)
115115
})
116+
117+
test_that("paste_linter skips allowed usages for file paths", {
118+
linter <- paste_linter()
119+
120+
expect_lint("paste('a', 'b', 'c')", NULL, linter)
121+
expect_lint("paste('a', 'b', 'c', sep = ',')", NULL, linter)
122+
expect_lint("paste('a', 'b', collapse = '/')", NULL, linter)
123+
expect_lint("cat(paste('a', 'b'), sep = '/')", NULL, linter)
124+
expect_lint("sep <- '/'; paste('a', sep)", NULL, linter)
125+
expect_lint("paste(sep = ',', '/', 'a')", NULL, linter)
126+
127+
# paste(..., sep='/', collapse=collapse) is not a trivial swap to file.path
128+
expect_lint("paste(x, y, sep = '/', collapse = ':')", NULL, linter)
129+
130+
expect_lint("file.path('a', 'b', 'c')", NULL, linter)
131+
132+
# testing the sep starts with / is not enough
133+
expect_lint("paste('a', 'b', sep = '//')", NULL, linter)
134+
})
135+
136+
test_that("paste_linter blocks simple disallowed usages for file paths", {
137+
linter <- paste_linter()
138+
lint_msg <- rex::rex("Construct file paths with file.path(...) instead of")
139+
140+
expect_lint("paste(sep = '/', 'a', 'b')", lint_msg, linter)
141+
expect_lint("paste('a', 'b', sep = '/')", lint_msg, linter)
142+
})
143+
144+
test_that("paste_linter ignores non-path cases with paste0", {
145+
linter <- paste_linter()
146+
147+
expect_lint("paste0(x, y)", NULL, linter)
148+
expect_lint("paste0('abc', 'def')", NULL, linter)
149+
expect_lint("paste0('/abc', 'def/')", NULL, linter)
150+
expect_lint("paste0(x, 'def/')", NULL, linter)
151+
expect_lint("paste0('/abc', y)", NULL, linter)
152+
expect_lint("paste0(foo(x), y)", NULL, linter)
153+
expect_lint("paste0(foo(x), 'def')", NULL, linter)
154+
155+
# these might be a different lint (as.character instead, e.g.) but not here
156+
expect_lint("paste0(x)", NULL, linter)
157+
expect_lint("paste0('a')", NULL, linter)
158+
expect_lint("paste0('a', 1)", NULL, linter)
159+
160+
# paste0(..., collapse=collapse) not directly mapped to file.path
161+
expect_lint("paste0(x, collapse = '/')", NULL, linter)
162+
})
163+
164+
test_that("paste_linter detects paths built with '/' and paste0", {
165+
linter <- paste_linter()
166+
lint_msg <- rex::rex("Construct file paths with file.path(...) instead of")
167+
168+
expect_lint("paste0(x, '/', y)", lint_msg, linter)
169+
expect_lint("paste0(x, '/', y, '/', z)", lint_msg, linter)
170+
expect_lint("paste0(x, '/abc/', 'def/', y)", lint_msg, linter)
171+
expect_lint("paste0(foo(x), '/abc/', 'def/', bar(y))", lint_msg, linter)
172+
})
173+
174+
test_that("paste_linter skips initial/terminal '/' and repeated '/' for paths", {
175+
linter <- paste_linter()
176+
177+
expect_lint("paste0('/', x)", NULL, linter)
178+
expect_lint("paste0(x, '/')", NULL, linter)
179+
expect_lint("paste0(x, '//hey/', y)", NULL, linter)
180+
expect_lint("paste0(x, '/hey//', y)", NULL, linter)
181+
})
182+
183+
test_that("paste_linter doesn't skip all initial/terminal '/' for paths", {
184+
linter <- paste_linter()
185+
lint_msg <- rex::rex("Construct file paths with file.path(...) instead of")
186+
187+
expect_lint('paste0("/abc/", "def")', lint_msg, linter)
188+
expect_lint('paste0("abc/", "def/")', lint_msg, linter)
189+
})
190+
191+
test_that("multiple path lints are generated correctly", {
192+
expect_lint(
193+
trim_some("{
194+
paste(x, y, sep = '/')
195+
paste0(x, '/', y)
196+
}"),
197+
list(
198+
rex::rex('paste(..., sep = "/")'),
199+
rex::rex('paste0(x, "/", y, "/", z)')
200+
),
201+
paste_linter()
202+
)
203+
})
204+
205+
test_that("allow_file_path argument works", {
206+
expect_lint("paste(x, y, sep = '/')", NULL, paste_linter(allow_file_path = TRUE))
207+
})

0 commit comments

Comments
 (0)