Skip to content

Commit 71beed9

Browse files
extend paste_linter() for strrep() equivalents (#1652)
* extend paste_linter() for strrep() equivalents * new tests * Update R/paste_linter.R Co-authored-by: Indrajeet Patil <[email protected]> * Update paste_linter.Rd Co-authored-by: Indrajeet Patil <[email protected]>
1 parent 09adcf3 commit 71beed9

File tree

4 files changed

+65
-8
lines changed

4 files changed

+65
-8
lines changed

NEWS.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,9 @@
3636

3737
* `pipe_continuation_linter()` recognizes violations involving the native R pipe `|>` (#1609, @MichaelChirico)
3838

39+
* `paste_linter()` also catches usages like `paste(rep("*", 10L), collapse = "")` that can be written more
40+
concisely as `strrep("*", 10L)` (#1108, @MichaelChirico)
41+
3942
### New linters
4043

4144
* `unnecessary_lambda_linter()`: detect unnecessary lambdas (anonymous functions), e.g.

R/paste_linter.R

Lines changed: 35 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,20 @@
11
#' Raise lints for several common poor usages of `paste()`
22
#'
33
#' The following issues are linted by default by this linter
4-
#' (and each can be turned off optionally):
4+
#' (see arguments for which can be de-activated optionally):
55
#'
66
#' 1. Block usage of [paste()] with `sep = ""`. [paste0()] is a faster, more concise alternative.
77
#' 2. Block usage of `paste()` or `paste0()` with `collapse = ", "`. [toString()] is a direct
88
#' wrapper for this, and alternatives like [glue::glue_collapse()] might give better messages for humans.
99
#' 3. Block usage of `paste0()` that supplies `sep=` -- this is not a formal argument to `paste0`, and
1010
#' is likely to be a mistake.
11+
#' 4. Block usage of `paste()` / `paste0()` combined with [rep()] that could be replaced by
12+
#' [strrep()]. `strrep()` can handle the task of building a block of repeated strings
13+
#' (e.g. often used to build "horizontal lines" for messages). This is both more readable and
14+
#' skips the (likely small) overhead of putting two strings into the global string cache when only one is needed.
15+
#'
16+
#' Only target scalar usages -- `strrep` can handle more complicated cases (e.g. `strrep(letters, 26:1)`,
17+
#' but those aren't as easily translated from a `paste(collapse=)` call.
1118
#'
1219
#' @evalRd rd_tags("paste_linter")
1320
#' @param allow_empty_sep Logical, default `FALSE`. If `TRUE`, usage of
@@ -40,19 +47,29 @@ paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
4047
/parent::expr
4148
"
4249

50+
paste_strrep_xpath <- "
51+
//SYMBOL_FUNCTION_CALL[text() = 'paste' or text() = 'paste0']
52+
/parent::expr[
53+
count(following-sibling::expr) = 2
54+
and following-sibling::expr[1][expr[1][SYMBOL_FUNCTION_CALL[text() = 'rep']] and expr[2][STR_CONST]]
55+
and following-sibling::SYMBOL_SUB[text() = 'collapse']
56+
]
57+
/parent::expr
58+
"
59+
4360
Linter(function(source_expression) {
4461
if (!is_lint_level(source_expression, "expression")) {
4562
return(list())
4663
}
4764

4865
xml <- source_expression$xml_parsed_content
49-
lints <- list()
66+
optional_lints <- list()
5067

5168
if (!allow_empty_sep) {
5269
empty_sep_expr <- xml2::xml_find_all(xml, sep_xpath)
5370
sep_value <- get_r_string(empty_sep_expr, xpath = "./SYMBOL_SUB[text() = 'sep']/following-sibling::expr[1]")
5471

55-
lints <- c(lints, xml_nodes_to_lints(
72+
optional_lints <- c(optional_lints, xml_nodes_to_lints(
5673
empty_sep_expr[!nzchar(sep_value)],
5774
source_expression = source_expression,
5875
lint_message = 'paste0(...) is better than paste(..., sep = "").',
@@ -68,7 +85,7 @@ paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
6885
xpath = "./SYMBOL_SUB[text() = 'collapse']/following-sibling::expr[1]"
6986
)
7087

71-
lints <- c(lints, xml_nodes_to_lints(
88+
optional_lints <- c(optional_lints, xml_nodes_to_lints(
7289
to_string_expr[collapse_value == ", "],
7390
source_expression = source_expression,
7491
lint_message = paste(
@@ -81,13 +98,24 @@ paste_linter <- function(allow_empty_sep = FALSE, allow_to_string = FALSE) {
8198
}
8299

83100
paste0_sep_expr <- xml2::xml_find_all(xml, paste0_sep_xpath)
84-
lints <- c(lints, xml_nodes_to_lints(
101+
paste0_sep_lints <- xml_nodes_to_lints(
85102
paste0_sep_expr,
86103
source_expression = source_expression,
87104
lint_message = "sep= is not a formal argument to paste0(); did you mean to use paste(), or collapse=?",
88105
type = "warning"
89-
))
106+
)
107+
108+
paste_strrep_expr <- xml2::xml_find_all(xml, paste_strrep_xpath)
109+
collapse_arg <- get_r_string(paste_strrep_expr, "SYMBOL_SUB/following-sibling::expr[1]/STR_CONST")
110+
paste_strrep_expr <- paste_strrep_expr[!nzchar(collapse_arg)]
111+
paste_call <- xp_call_name(paste_strrep_expr)
112+
paste_strrep_lints <- xml_nodes_to_lints(
113+
paste_strrep_expr,
114+
source_expression = source_expression,
115+
lint_message = sprintf('strrep(x, times) is better than %s(rep(x, times), collapse = "").', paste_call),
116+
type = "warning"
117+
)
90118

91-
lints
119+
c(optional_lints, paste0_sep_lints, paste_strrep_lints)
92120
})
93121
}

man/paste_linter.Rd

Lines changed: 8 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: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,3 +89,22 @@ test_that("paste_linter catches use of paste0 with sep=", {
8989
paste_linter()
9090
)
9191
})
92+
93+
test_that("paste_linter skips allowed usages for strrep()", {
94+
expect_lint("paste(x, collapse = '')", NULL, paste_linter())
95+
expect_lint("paste(rep('*', 10), collapse = '+')", NULL, paste_linter())
96+
expect_lint("paste(rep(c('a', 'b'), 2), collapse = '')", NULL, paste_linter())
97+
expect_lint("paste0(rep('a', 2), 'b', collapse = '')", NULL, paste_linter())
98+
# no collapse
99+
expect_lint("paste(rep('*', 10))", NULL, paste_linter())
100+
# combined before aggregating
101+
expect_lint("paste(rep('*', 10), rep('x', 10), collapse = '')", NULL, paste_linter())
102+
})
103+
104+
test_that("paste_linter blocks simple disallowed usages", {
105+
linter <- paste_linter()
106+
lint_msg <- rex::rex("strrep(x, times) is better than paste")
107+
108+
expect_lint("paste0(rep('*', 20L), collapse='')", lint_msg, linter)
109+
expect_lint("paste(rep('#', width), collapse='')", lint_msg, linter)
110+
})

0 commit comments

Comments
 (0)