Skip to content

Commit d695796

Browse files
Lint for paste0(collapse='') instead of paste(collapse='') (#2559)
* Lint for paste0(collapse='') instead of paste(collapse='') * Fix in {lintr} * Also skip on '...', thanks to base R * roxygenize * trailing whitespace
1 parent 28166bf commit d695796

File tree

9 files changed

+85
-21
lines changed

9 files changed

+85
-21
lines changed

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@
5151
* `vector_logic_linter()` is extended to recognize incorrect usage of scalar operators `&&` and `||` inside subsetting expressions like `dplyr::filter(x, A && B)` (#2166, @MichaelChirico).
5252
* `any_is_na_linter()` is extended to catch the unusual usage `NA %in% x` (#2113, @MichaelChirico).
5353
* `make_linter_from_xpath()` errors up front when `lint_message` is missing (instead of delaying this error until the linter is used, #2541, @MichaelChirico).
54+
* `paste_linter()` is extended to recommend using `paste()` instead of `paste0()` for simply aggregating a character vector with `collapse=`, i.e., when `sep=` is irrelevant (#1108, @MichaelChirico).
5455

5556
### New linters
5657

R/deprecated.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,6 @@ lintr_deprecated <- function(what, alternative = NULL, version = NULL,
1515
". ",
1616
if (length(alternative) > 0L) c("Use ", alternative, " instead.")
1717
)
18-
msg <- paste0(msg, collapse = "")
18+
msg <- paste(msg, collapse = "")
1919
signal(msg, call. = FALSE, domain = NA)
2020
}

R/expect_lint.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,7 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
6161

6262
lints <- lint(file, ...)
6363
n_lints <- length(lints)
64-
lint_str <- if (n_lints) paste0(c("", lints), collapse = "\n") else ""
64+
lint_str <- if (n_lints) paste(c("", lints), collapse = "\n") else ""
6565

6666
wrong_number_fmt <- "got %d lints instead of %d%s"
6767
if (is.null(checks)) {

R/lint.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -666,7 +666,7 @@ highlight_string <- function(message, column_number = NULL, ranges = NULL) {
666666
}
667667

668668
fill_with <- function(character = " ", length = 1L) {
669-
paste0(collapse = "", rep.int(character, length))
669+
paste(collapse = "", rep.int(character, length))
670670
}
671671

672672
has_positional_logical <- function(dots) {

R/paste_linter.R

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,11 @@
5858
#' linters = paste_linter(allow_file_path = "never")
5959
#' )
6060
#'
61+
#' lint(
62+
#' text = 'paste0(x, collapse = "")',
63+
#' linters = paste_linter()
64+
#' )
65+
#'
6166
#' # okay
6267
#' lint(
6368
#' text = 'paste0("a", "b")',
@@ -99,6 +104,11 @@
99104
#' linters = paste_linter()
100105
#' )
101106
#'
107+
#' lint(
108+
#' text = 'paste(x, collapse = "")',
109+
#' linters = paste_linter()
110+
#' )
111+
#'
102112
#' @seealso [linters] for a complete list of linters available in lintr.
103113
#' @export
104114
paste_linter <- function(allow_empty_sep = FALSE,
@@ -157,6 +167,15 @@ paste_linter <- function(allow_empty_sep = FALSE,
157167
empty_paste_note <-
158168
'Note that paste() converts empty inputs to "", whereas file.path() leaves it empty.'
159169

170+
paste0_collapse_xpath <- "
171+
parent::expr
172+
/parent::expr[
173+
SYMBOL_SUB[text() = 'collapse']
174+
and count(expr) = 3
175+
and not(expr/SYMBOL[text() = '...'])
176+
]
177+
"
178+
160179
Linter(linter_level = "expression", function(source_expression) {
161180
paste_calls <- source_expression$xml_find_function_calls("paste")
162181
paste0_calls <- source_expression$xml_find_function_calls("paste0")
@@ -219,6 +238,14 @@ paste_linter <- function(allow_empty_sep = FALSE,
219238
type = "warning"
220239
)
221240

241+
paste0_collapse_expr <- xml_find_all(paste0_calls, paste0_collapse_xpath)
242+
paste0_collapse_lints <- xml_nodes_to_lints(
243+
paste0_collapse_expr,
244+
source_expression = source_expression,
245+
lint_message = "Use paste(), not paste0(), to collapse a character vector when sep= is not used.",
246+
type = "warning"
247+
)
248+
222249
if (check_file_paths) {
223250
paste_sep_slash_expr <- paste_sep_expr[paste_sep_value == "/"]
224251
optional_lints <- c(optional_lints, xml_nodes_to_lints(
@@ -248,7 +275,7 @@ paste_linter <- function(allow_empty_sep = FALSE,
248275
))
249276
}
250277

251-
c(optional_lints, paste0_sep_lints, paste_strrep_lints)
278+
c(optional_lints, paste0_sep_lints, paste_strrep_lints, paste0_collapse_lints)
252279
})
253280
}
254281

R/utils.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@ get_content <- function(lines, info) {
111111
lines[length(lines)] <- substr(lines[length(lines)], 1L, info$col2)
112112
lines[1L] <- substr(lines[1L], info$col1, nchar(lines[1L]))
113113
}
114-
paste0(collapse = "\n", lines)
114+
paste(lines, collapse = "\n")
115115
}
116116

117117
logical_env <- function(x) {

man/paste_linter.Rd

Lines changed: 10 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-lint.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ test_that("lint() results from file or text should be consistent", {
117117
linters <- list(assignment_linter(), infix_spaces_linter())
118118
lines <- c("x<-1", "x+1")
119119
file <- withr::local_tempfile(lines = lines)
120-
text <- paste0(lines, collapse = "\n")
120+
text <- paste(lines, collapse = "\n")
121121
file <- normalizePath(file)
122122

123123
lint_from_file <- lint(file, linters = linters)

tests/testthat/test-paste_linter.R

Lines changed: 41 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -52,20 +52,13 @@ test_that("paste_linter blocks simple disallowed usages for collapse=', '", {
5252
rex::rex('toString(.) is more expressive than paste(., collapse = ", ")'),
5353
paste_linter()
5454
)
55-
56-
expect_lint(
57-
"paste0(foo(x), collapse = ', ')",
58-
rex::rex('toString(.) is more expressive than paste(., collapse = ", ")'),
59-
paste_linter()
60-
)
6155
})
6256

6357
test_that("paste_linter respects non-default arguments", {
6458
expect_lint("paste(sep = '', 'a', 'b')", NULL, paste_linter(allow_empty_sep = TRUE))
6559
expect_lint("paste('a', 'b', sep = '')", NULL, paste_linter(allow_empty_sep = TRUE))
6660

6761
expect_lint("paste(collapse = ', ', x)", NULL, paste_linter(allow_to_string = TRUE))
68-
expect_lint("paste0(foo(x), collapse = ', ')", NULL, paste_linter(allow_to_string = TRUE))
6962
})
7063

7164
test_that("paste_linter works for raw strings", {
@@ -107,11 +100,11 @@ test_that("paste_linter skips allowed usages for strrep()", {
107100
})
108101

109102
test_that("paste_linter blocks simple disallowed usages", {
110-
linter <- paste_linter()
111-
lint_msg <- rex::rex("strrep(x, times) is better than paste")
112-
113-
expect_lint("paste0(rep('*', 20L), collapse='')", lint_msg, linter)
114-
expect_lint("paste(rep('#', width), collapse='')", lint_msg, linter)
103+
expect_lint(
104+
"paste(rep('#', width), collapse='')",
105+
rex::rex("strrep(x, times) is better than paste"),
106+
paste_linter()
107+
)
115108
})
116109

117110
test_that("paste_linter skips allowed usages for file paths", {
@@ -156,9 +149,6 @@ test_that("paste_linter ignores non-path cases with paste0", {
156149
expect_lint("paste0(x)", NULL, linter)
157150
expect_lint("paste0('a')", NULL, linter)
158151
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)
162152
})
163153

164154
test_that("paste_linter detects paths built with '/' and paste0", {
@@ -245,3 +235,39 @@ test_that("raw strings are detected in file path logic", {
245235
expect_lint("paste(x, y, sep = R'{//}')", NULL, linter)
246236
expect_lint("paste(x, y, sep = R'{/}')", lint_msg, linter)
247237
})
238+
239+
test_that("paste0(collapse=...) is caught", {
240+
linter <- paste_linter()
241+
lint_msg <- rex::rex("Use paste(), not paste0(), to collapse a character vector when sep= is not used.")
242+
243+
expect_lint("paste(x, collapse = '')", NULL, linter)
244+
expect_lint("paste0(a, b, collapse = '')", NULL, linter)
245+
# pass-through can pass any number of arguments
246+
expect_lint("paste0(..., collapse = '')", NULL, linter)
247+
expect_lint("paste0(x, collapse = '')", lint_msg, linter)
248+
expect_lint("paste0(x, collapse = 'xxx')", lint_msg, linter)
249+
expect_lint("paste0(foo(x, y, z), collapse = '')", lint_msg, linter)
250+
})
251+
252+
test_that("paste0(collapse=...) cases interacting with other rules are handled", {
253+
linter <- paste_linter()
254+
lint_msg <- rex::rex("Use paste(), not paste0(), to collapse a character vector when sep= is not used.")
255+
256+
# multiple lints when collapse= happens to be ", "
257+
expect_lint(
258+
"paste0(foo(x), collapse = ', ')",
259+
list(rex::rex('toString(.) is more expressive than paste(., collapse = ", ")'), lint_msg),
260+
linter
261+
)
262+
expect_lint("paste0(foo(x), collapse = ', ')", lint_msg, paste_linter(allow_to_string = TRUE))
263+
264+
expect_lint(
265+
"paste0(rep('*', 20L), collapse='')",
266+
list(rex::rex("strrep(x, times) is better than paste"), lint_msg),
267+
linter
268+
)
269+
270+
# paste0(..., collapse=collapse) not directly mapped to file.path
271+
expect_lint("paste0(x, collapse = '/')", lint_msg, linter)
272+
expect_lint("paste0(x, y, collapse = '/')", NULL, linter)
273+
})

0 commit comments

Comments
 (0)