Skip to content

Commit 8783914

Browse files
Update sprintf_linter() to lint constant strings (#2894)
* Update sprintf_linter() tests to lint constant strings * Factor out fmt_by_name_xpath * Do not test for string fmt in in_pipe_xpath * Add lint to detect constant strings in sprintf * Fix constant sprintf call() in lintr codebase * Simplify call_xpath() Since it is now handled by !is.na(fmt) * Use fmt_by_name_xpath directly without assigning * Remove nested ifelse() * Add example for new lint * Remove unnecessary glue() call * Use expect_no_lint() where appropriate * Add test for constant '%' * Test and handle %% case better * Use actual function name in lint message * Convert one more expect_lint(, NULL, ) * Support comments at various positions * Use action/reason format for message * Use dedicated xp_call_name() function to get fct_name * Document new sprintf_linter() lints in NEWS * one line in NEWS --------- Co-authored-by: Michael Chirico <[email protected]>
1 parent 38db1ac commit 8783914

File tree

5 files changed

+91
-35
lines changed

5 files changed

+91
-35
lines changed

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@
4747
* `fixed_regex_linter()` recognizes usage of the new (R 4.5.0) `grepv()` wrapper of `grep()`; `regex_subset_linter()` also recommends `grepv()` alternatives (#2855, @MichaelChirico).
4848
* `object_usage_linter()` lints missing packages that may cause false positives (#2872, @AshesITR)
4949
* New argument `include_s4_slots` for the `xml_find_function_calls()` entry in the `get_source_expressions()` to govern whether calls of the form `s4Obj@fun()` are included in the result (#2820, @MichaelChirico).
50+
* `sprintf_linter()` lints `sprintf()` and `gettextf()` calls when a constant string is passed to `fmt` (#2894, @Bisaloo).
5051

5152
### New linters
5253

R/expect_length_linter.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,13 +22,13 @@
2222
#' @export
2323
expect_length_linter <- function() {
2424
# TODO(#2465): also catch expect_true(length(x) == 1)
25-
xpath <- sprintf("
25+
xpath <- "
2626
following-sibling::expr[
2727
expr[1][SYMBOL_FUNCTION_CALL[text() = 'length']]
2828
and (position() = 1 or preceding-sibling::expr[NUM_CONST])
2929
]
3030
/parent::expr[not(SYMBOL_SUB[text() = 'info' or contains(text(), 'label')])]
31-
")
31+
"
3232

3333
Linter(linter_level = "expression", function(source_expression) {
3434
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))

R/sprintf_linter.R

Lines changed: 40 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,11 @@
1212
#' linters = sprintf_linter()
1313
#' )
1414
#'
15+
#' lint(
16+
#' text = 'sprintf("hello")',
17+
#' linters = sprintf_linter()
18+
#' )
19+
#'
1520
#' # okay
1621
#' lint(
1722
#' text = 'sprintf("hello %s %s %d", x, y, z)',
@@ -29,21 +34,15 @@
2934
sprintf_linter <- function() {
3035
call_xpath <- "
3136
parent::expr[
32-
(
33-
OP-LEFT-PAREN/following-sibling::expr[1]/STR_CONST or
34-
SYMBOL_SUB[text() = 'fmt']/following-sibling::expr[1]/STR_CONST
35-
) and
3637
not(expr/SYMBOL[text() = '...'])
3738
]"
3839

3940
pipes <- setdiff(magrittr_pipes, "%$%")
40-
in_pipe_xpath <- glue("self::expr[
41-
preceding-sibling::*[1][self::PIPE or self::SPECIAL[{ xp_text_in_table(pipes) }]]
42-
and (
43-
preceding-sibling::*[2]/STR_CONST
44-
or SYMBOL_SUB[text() = 'fmt']/following-sibling::expr[1]/STR_CONST
45-
)
46-
]")
41+
in_pipe_xpath <- glue(
42+
"self::expr[
43+
preceding-sibling::*[not(self::COMMENT)][1][self::PIPE or self::SPECIAL[{ xp_text_in_table(pipes) }]]
44+
]"
45+
)
4746

4847
is_missing <- function(x) is.symbol(x) && !nzchar(x)
4948

@@ -89,7 +88,7 @@ sprintf_linter <- function() {
8988
arg_idx <- 2L:length(parsed_expr)
9089
parsed_expr[arg_idx + 1L] <- parsed_expr[arg_idx]
9190
names(parsed_expr)[arg_idx + 1L] <- arg_names[arg_idx]
92-
parsed_expr[[2L]] <- xml2lang(xml_find_first(xml, "preceding-sibling::*[2]"))
91+
parsed_expr[[2L]] <- xml2lang(xml_find_first(xml, "preceding-sibling::*[not(self::COMMENT)][2]"))
9392
names(parsed_expr)[2L] <- ""
9493
}
9594
parsed_expr <- zap_extra_args(parsed_expr)
@@ -104,15 +103,41 @@ sprintf_linter <- function() {
104103
Linter(linter_level = "file", function(source_expression) {
105104
xml_calls <- source_expression$xml_find_function_calls(c("sprintf", "gettextf"))
106105
sprintf_calls <- xml_find_all(xml_calls, call_xpath)
106+
in_pipeline <- !is.na(xml_find_first(sprintf_calls, in_pipe_xpath))
107+
108+
fmt_by_name <- get_r_string(
109+
sprintf_calls,
110+
"SYMBOL_SUB[text() = 'fmt']/following-sibling::expr[1]/STR_CONST"
111+
)
112+
fmt_by_pos <- ifelse(
113+
in_pipeline,
114+
get_r_string(sprintf_calls, "preceding-sibling::*[not(self::COMMENT)][2]/STR_CONST"),
115+
get_r_string(sprintf_calls, "OP-LEFT-PAREN/following-sibling::expr[1]/STR_CONST")
116+
)
107117

108-
sprintf_warning <- vapply(sprintf_calls, capture_sprintf_warning, character(1L))
118+
fmt <- ifelse(!is.na(fmt_by_name), fmt_by_name, fmt_by_pos)
119+
constant_fmt <- !is.na(fmt) & !grepl("%", gsub("%%", "", fmt, fixed = TRUE), fixed = TRUE)
120+
121+
fct_name <- xp_call_name(sprintf_calls)
122+
123+
constant_fmt_lint <- xml_nodes_to_lints(
124+
sprintf_calls[constant_fmt],
125+
source_expression = source_expression,
126+
lint_message = sprintf("%s call can be removed when a constant string is provided.", fct_name[constant_fmt]),
127+
type = "warning"
128+
)
129+
130+
templated_sprintf_calls <- sprintf_calls[!constant_fmt & !is.na(fmt)]
131+
sprintf_warning <- vapply(templated_sprintf_calls, capture_sprintf_warning, character(1L))
109132

110133
has_warning <- !is.na(sprintf_warning)
111-
xml_nodes_to_lints(
112-
sprintf_calls[has_warning],
134+
invalid_sprintf_lint <- xml_nodes_to_lints(
135+
templated_sprintf_calls[has_warning],
113136
source_expression = source_expression,
114137
lint_message = sprintf_warning[has_warning],
115138
type = "warning"
116139
)
140+
141+
c(constant_fmt_lint, invalid_sprintf_lint)
117142
})
118143
}

man/sprintf_linter.Rd

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

tests/testthat/test-sprintf_linter.R

Lines changed: 43 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -4,14 +4,13 @@ patrick::with_parameters_test_that(
44
linter <- sprintf_linter()
55

66
# NB: using paste0, not sprintf, to avoid escaping '%d' in sprint fmt=
7-
expect_lint(paste0(call_name, "('hello')"), NULL, linter)
8-
expect_lint(paste0(call_name, "('hello %d', 1)"), NULL, linter)
9-
expect_lint(paste0(call_name, "('hello %d', x)"), NULL, linter)
10-
expect_lint(paste0(call_name, "('hello %d', x + 1)"), NULL, linter)
11-
expect_lint(paste0(call_name, "('hello %d', f(x))"), NULL, linter)
12-
expect_lint(paste0(call_name, "('hello %1$s %1$s', x)"), NULL, linter)
13-
expect_lint(paste0(call_name, "('hello %1$s %1$s %2$d', x, y)"), NULL, linter)
14-
expect_lint(paste0(call_name, "('hello %1$s %1$s %2$d %3$s', x, y, 1.5)"), NULL, linter)
7+
expect_no_lint(paste0(call_name, "('hello %d', 1)"), linter)
8+
expect_no_lint(paste0(call_name, "('hello %d', x)"), linter)
9+
expect_no_lint(paste0(call_name, "('hello %d', x + 1)"), linter)
10+
expect_no_lint(paste0(call_name, "('hello %d', f(x))"), linter)
11+
expect_no_lint(paste0(call_name, "('hello %1$s %1$s', x)"), linter)
12+
expect_no_lint(paste0(call_name, "('hello %1$s %1$s %2$d', x, y)"), linter)
13+
expect_no_lint(paste0(call_name, "('hello %1$s %1$s %2$d %3$s', x, y, 1.5)"), linter)
1514
},
1615
.test_name = c("sprintf", "gettextf"),
1716
call_name = c("sprintf", "gettextf")
@@ -23,7 +22,13 @@ patrick::with_parameters_test_that(
2322
linter <- sprintf_linter()
2423
unused_arg_msg <- if (getRversion() >= "4.1.0") "one argument not used by format" else NULL
2524

26-
expect_lint(paste0(call_name, "('hello', 1)"), unused_arg_msg, linter)
25+
expect_lint(paste0(call_name, "('hello', 1)"), "constant", linter)
26+
27+
expect_lint(paste0(call_name, "('hello')"), "constant", linter)
28+
expect_lint(paste0(call_name, "('100%% automated')"), "constant", linter)
29+
expect_lint(paste0(call_name, "('100%%%% automated')"), "constant", linter)
30+
expect_lint(paste0(call_name, "('100%%%s')"), "too few", linter)
31+
expect_lint(paste0(call_name, "('100%%%%s', x)"), "constant", linter)
2732

2833
expect_lint(
2934
paste0(call_name, "('hello %d', 'a')"),
@@ -66,24 +71,42 @@ test_that("edge cases are detected correctly", {
6671
linter <- sprintf_linter()
6772

6873
# works with multi-line sprintf and comments
69-
expect_lint(
74+
expect_no_lint(
7075
trim_some("
7176
sprintf(
7277
'test fmt %s', # this is a comment
7378
2
7479
)
7580
"),
76-
NULL,
81+
linter
82+
)
83+
84+
expect_no_lint(
85+
trim_some("
86+
'test fmt %s' |> # this is a pipe comment
87+
sprintf( # this is an opening comment
88+
2 # this is a mid-call comment
89+
)
90+
"),
91+
linter
92+
)
93+
94+
expect_lint(
95+
trim_some("
96+
'test fmt' |> # this is a pipe comment
97+
sprintf()
98+
"),
99+
"constant",
77100
linter
78101
)
79102

80103
# dots
81-
expect_lint("sprintf('%d %d, %d', id, ...)", NULL, linter)
104+
expect_no_lint("sprintf('%d %d, %d', id, ...)", linter)
82105

83106
# TODO(#1265) extend ... detection to at least test for too many arguments.
84107

85108
# named argument fmt
86-
expect_lint("sprintf(x, fmt = 'hello %1$s %1$s')", NULL, linter)
109+
expect_no_lint("sprintf(x, fmt = 'hello %1$s %1$s')", linter)
87110

88111
expect_lint(
89112
"sprintf(x, fmt = 'hello %1$s %1$s %3$d', y)",
@@ -92,7 +115,9 @@ test_that("edge cases are detected correctly", {
92115
)
93116

94117
# #2131: xml2lang stripped necessary whitespace
95-
expect_lint("sprintf('%s', if (A) '' else y)", NULL, linter)
118+
expect_no_lint("sprintf('%s', if (A) '' else y)", linter)
119+
120+
expect_no_lint("sprintf('100%%%s', x)", linter)
96121
})
97122

98123
local({
@@ -103,17 +128,17 @@ local({
103128
patrick::with_parameters_test_that(
104129
"piping into sprintf works",
105130
{
106-
expect_lint(paste("x", pipe, "sprintf(fmt = '%s')"), NULL, linter)
131+
expect_no_lint(paste("x", pipe, "sprintf(fmt = '%s')"), linter)
107132
# no fmt= specified -> this is just 'sprintf("%s", "%s%s")', which won't lint
108-
expect_lint(paste('"%s"', pipe, 'sprintf("%s%s")'), NULL, linter)
133+
expect_no_lint(paste('"%s"', pipe, 'sprintf("%s%s")'), linter)
109134
expect_lint(paste("x", pipe, "sprintf(fmt = '%s%s')"), unused_fmt_msg, linter)
110135

111136
# Cannot evaluate statically --> skip
112-
expect_lint(paste("x", pipe, 'sprintf("a")'), NULL, linter)
137+
expect_no_lint(paste("x", pipe, 'sprintf("a")'), linter)
113138
# Nested pipes
114139
expect_lint(
115140
paste("'%%sb'", pipe, "sprintf('%s')", pipe, "sprintf('a')"),
116-
if (getRversion() >= "4.1.0") list(column_number = nchar(paste("'%%sb'", pipe, "x")), message = unused_arg_msg),
141+
if (getRversion() >= "4.1.0") list(column_number = nchar(paste("'%%sb'", pipe, "x")), message = "constant"),
117142
linter
118143
)
119144
expect_lint(

0 commit comments

Comments
 (0)