Skip to content

Commit 618a527

Browse files
Robust linters for comments in "natural" places (#2902)
* Robust linters for comments in "natural" places * revert whats in #2900 already * missed file not matching linter names
1 parent 8783914 commit 618a527

16 files changed

+209
-70
lines changed

R/conjunct_test_linter.R

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,8 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE,
8282
following-sibling::expr[1][AND2]
8383
/parent::expr
8484
"
85-
named_stopifnot_condition <- if (allow_named_stopifnot) "and not(preceding-sibling::*[1][self::EQ_SUB])" else ""
85+
named_stopifnot_condition <-
86+
if (allow_named_stopifnot) "and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])" else ""
8687
stopifnot_xpath <- glue("
8788
following-sibling::expr[1][AND2 {named_stopifnot_condition}]
8889
/parent::expr

R/fixed_regex_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {
120120
and not({ in_pipe_cond })
121121
) or (
122122
STR_CONST
123-
and preceding-sibling::*[2][self::SYMBOL_SUB/text() = 'pattern']
123+
and preceding-sibling::*[not(self::COMMENT)][2][self::SYMBOL_SUB/text() = 'pattern']
124124
)
125125
]
126126
")

R/outer_negation_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ outer_negation_linter <- function() {
4444
not(expr[
4545
position() > 1
4646
and not(OP-EXCLAMATION)
47-
and not(preceding-sibling::*[1][self::EQ_SUB])
47+
and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])
4848
])
4949
]
5050
"

R/shared_constants.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -220,7 +220,7 @@ object_name_xpath <- local({
220220
]"
221221

222222
# either an argument supplied positionally, i.e., not like 'arg = val', or the call <expr>
223-
not_kwarg_cond <- "not(preceding-sibling::*[1][self::EQ_SUB])"
223+
not_kwarg_cond <- "not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])"
224224

225225
glue(xp_strip_comments("
226226
//SYMBOL[ {sprintf(xp_assignment_target_fmt, 'ancestor', '')} ]

R/unnecessary_concatenation_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ unnecessary_concatenation_linter <- function(allow_single_expression = TRUE) { #
6666

6767
pipes <- setdiff(magrittr_pipes, "%$%")
6868
to_pipe_xpath <- glue("
69-
./preceding-sibling::*[1][
69+
./preceding-sibling::*[not(self::COMMENT)][1][
7070
self::PIPE or
7171
self::SPECIAL[{ xp_text_in_table(pipes) }]
7272
]

R/unnecessary_lambda_linter.R

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -125,10 +125,14 @@ unnecessary_lambda_linter <- function(allow_comparison = FALSE) {
125125
.//expr[
126126
position() = 2
127127
and preceding-sibling::expr/SYMBOL_FUNCTION_CALL
128-
and not(preceding-sibling::*[1][self::EQ_SUB])
128+
and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])
129129
and not(parent::expr[
130130
preceding-sibling::expr[not(SYMBOL_FUNCTION_CALL)]
131-
or following-sibling::*[not(self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACE)]
131+
or following-sibling::*[not(
132+
self::OP-RIGHT-PAREN
133+
or self::OP-RIGHT-BRACE
134+
or self::COMMENT
135+
)]
132136
])
133137
]/SYMBOL
134138
]
@@ -143,7 +147,12 @@ unnecessary_lambda_linter <- function(allow_comparison = FALSE) {
143147
purrr_fun_xpath <- glue("
144148
following-sibling::expr[
145149
OP-TILDE
146-
and expr[OP-LEFT-PAREN/following-sibling::expr[1][not(preceding-sibling::*[2][self::SYMBOL_SUB])]/{purrr_symbol}]
150+
and expr
151+
/OP-LEFT-PAREN
152+
/following-sibling::expr[1][
153+
not(preceding-sibling::*[not(self::COMMENT)][2][self::SYMBOL_SUB])
154+
]
155+
/{purrr_symbol}
147156
and not(expr/OP-LEFT-PAREN/following-sibling::expr[position() > 1]//{purrr_symbol})
148157
]")
149158

R/unnecessary_nesting_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -234,7 +234,7 @@ unnecessary_nesting_linter <- function(
234234
# catch if (cond) { if (other_cond) { ... } }
235235
# count(*): only OP-LEFT-BRACE, one <expr>, and OP-RIGHT-BRACE.
236236
# Note that third node could be <expr_or_assign_or_help>.
237-
"following-sibling::expr[OP-LEFT-BRACE and count(*) = 3]/expr[IF and not(ELSE)]"
237+
"following-sibling::expr[OP-LEFT-BRACE and count(*) - count(COMMENT) = 3]/expr[IF and not(ELSE)]"
238238
),
239239
collapse = " | "
240240
)

tests/testthat/test-conjunct_test_linter.R

Lines changed: 43 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,25 @@
11
test_that("conjunct_test_linter skips allowed usages of expect_true", {
2-
expect_lint("expect_true(x)", NULL, conjunct_test_linter())
3-
expect_lint("testthat::expect_true(x, y, z)", NULL, conjunct_test_linter())
2+
linter <- conjunct_test_linter()
3+
4+
expect_no_lint("expect_true(x)", linter)
5+
expect_no_lint("testthat::expect_true(x, y, z)", linter)
46

57
# more complicated expression
6-
expect_lint("expect_true(x || (y && z))", NULL, conjunct_test_linter())
8+
expect_no_lint("expect_true(x || (y && z))", linter)
79
# the same by operator precedence, though not obvious a priori
8-
expect_lint("expect_true(x || y && z)", NULL, conjunct_test_linter())
9-
expect_lint("expect_true(x && y || z)", NULL, conjunct_test_linter())
10+
expect_no_lint("expect_true(x || y && z)", linter)
11+
expect_no_lint("expect_true(x && y || z)", linter)
1012
})
1113

1214
test_that("conjunct_test_linter skips allowed usages of expect_true", {
13-
expect_lint("expect_false(x)", NULL, conjunct_test_linter())
14-
expect_lint("testthat::expect_false(x, y, z)", NULL, conjunct_test_linter())
15+
linter <- conjunct_test_linter()
16+
17+
expect_no_lint("expect_false(x)", linter)
18+
expect_no_lint("testthat::expect_false(x, y, z)", linter)
1519

1620
# more complicated expression
1721
# (NB: xx && yy || zz and xx || yy && zz both parse with || first)
18-
expect_lint("expect_false(x && (y || z))", NULL, conjunct_test_linter())
22+
expect_no_lint("expect_false(x && (y || z))", linter)
1923
})
2024

2125
test_that("conjunct_test_linter blocks && conditions with expect_true()", {
@@ -43,14 +47,14 @@ test_that("conjunct_test_linter blocks || conditions with expect_false()", {
4347
test_that("conjunct_test_linter skips allowed stopifnot() and assert_that() usages", {
4448
linter <- conjunct_test_linter()
4549

46-
expect_lint("stopifnot(x)", NULL, linter)
47-
expect_lint("assert_that(x, y, z)", NULL, linter)
50+
expect_no_lint("stopifnot(x)", linter)
51+
expect_no_lint("assert_that(x, y, z)", linter)
4852

4953
# more complicated expression
50-
expect_lint("stopifnot(x || (y && z))", NULL, linter)
54+
expect_no_lint("stopifnot(x || (y && z))", linter)
5155
# the same by operator precedence, though not obvious a priori
52-
expect_lint("stopifnot(x || y && z)", NULL, linter)
53-
expect_lint("assertthat::assert_that(x && y || z)", NULL, linter)
56+
expect_no_lint("stopifnot(x || y && z)", linter)
57+
expect_no_lint("assertthat::assert_that(x && y || z)", linter)
5458
})
5559

5660
test_that("conjunct_test_linter blocks simple disallowed usages of stopifnot() and assert_that()", {
@@ -66,12 +70,23 @@ test_that("conjunct_test_linter blocks simple disallowed usages of stopifnot() a
6670
})
6771

6872
test_that("conjunct_test_linter's allow_named_stopifnot argument works", {
73+
linter <- conjunct_test_linter()
74+
6975
# allowed by default
70-
expect_lint(
76+
expect_no_lint(
7177
"stopifnot('x must be a logical scalar' = length(x) == 1 && is.logical(x) && !is.na(x))",
72-
NULL,
73-
conjunct_test_linter()
78+
linter
7479
)
80+
# including with intervening comment
81+
expect_no_lint(
82+
trim_some("
83+
stopifnot('x must be a logical scalar' = # comment
84+
length(x) == 1 && is.logical(x) && !is.na(x)
85+
)
86+
"),
87+
linter
88+
)
89+
7590
expect_lint(
7691
"stopifnot('x is a logical scalar' = length(x) == 1 && is.logical(x) && !is.na(x))",
7792
rex::rex("Write multiple conditions like stopifnot(A, B)"),
@@ -82,11 +97,11 @@ test_that("conjunct_test_linter's allow_named_stopifnot argument works", {
8297
test_that("conjunct_test_linter skips allowed usages", {
8398
linter <- conjunct_test_linter()
8499

85-
expect_lint("dplyr::filter(DF, A, B)", NULL, linter)
86-
expect_lint("dplyr::filter(DF, !(A & B))", NULL, linter)
100+
expect_no_lint("dplyr::filter(DF, A, B)", linter)
101+
expect_no_lint("dplyr::filter(DF, !(A & B))", linter)
87102
# | is the "top-level" operator here
88-
expect_lint("dplyr::filter(DF, A & B | C)", NULL, linter)
89-
expect_lint("dplyr::filter(DF, A | B & C)", NULL, linter)
103+
expect_no_lint("dplyr::filter(DF, A & B | C)", linter)
104+
expect_no_lint("dplyr::filter(DF, A | B & C)", linter)
90105
})
91106

92107
test_that("conjunct_test_linter blocks simple disallowed usages", {
@@ -105,22 +120,22 @@ test_that("conjunct_test_linter respects its allow_filter argument", {
105120
linter_dplyr <- conjunct_test_linter(allow_filter = "not_dplyr")
106121
lint_msg <- rex::rex("Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B)")
107122

108-
expect_lint("dplyr::filter(DF, A & B)", NULL, linter_always)
109-
expect_lint("dplyr::filter(DF, A & B & C)", NULL, linter_always)
110-
expect_lint("DF %>% dplyr::filter(A & B)", NULL, linter_always)
123+
expect_no_lint("dplyr::filter(DF, A & B)", linter_always)
124+
expect_no_lint("dplyr::filter(DF, A & B & C)", linter_always)
125+
expect_no_lint("DF %>% dplyr::filter(A & B)", linter_always)
111126
expect_lint("dplyr::filter(DF, A & B)", lint_msg, linter_dplyr)
112127
expect_lint("dplyr::filter(DF, A & B & C)", lint_msg, linter_dplyr)
113128
expect_lint("DF %>% dplyr::filter(A & B)", lint_msg, linter_dplyr)
114-
expect_lint("filter(DF, A & B)", NULL, linter_dplyr)
115-
expect_lint("filter(DF, A & B & C)", NULL, linter_dplyr)
116-
expect_lint("DF %>% filter(A & B)", NULL, linter_dplyr)
129+
expect_no_lint("filter(DF, A & B)", linter_dplyr)
130+
expect_no_lint("filter(DF, A & B & C)", linter_dplyr)
131+
expect_no_lint("DF %>% filter(A & B)", linter_dplyr)
117132
})
118133

119134
test_that("filter() is assumed to be dplyr::filter() by default, unless o/w specified", {
120135
linter <- conjunct_test_linter()
121136

122-
expect_lint("stats::filter(A & B)", NULL, linter)
123-
expect_lint("ns::filter(A & B)", NULL, linter)
137+
expect_no_lint("stats::filter(A & B)", linter)
138+
expect_no_lint("ns::filter(A & B)", linter)
124139
expect_lint(
125140
"DF %>% filter(A & B)",
126141
rex::rex("Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B)"),

tests/testthat/test-fixed_regex_linter.R

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -352,13 +352,13 @@ test_that("'unescaped' regex can optionally be skipped", {
352352
})
353353

354354
local({
355+
linter <- fixed_regex_linter()
356+
lint_msg <- "This regular expression is static"
355357
pipes <- pipes(exclude = c("%$%", "%T>%"))
358+
356359
patrick::with_parameters_test_that(
357360
"linter is pipe-aware",
358361
{
359-
linter <- fixed_regex_linter()
360-
lint_msg <- "This regular expression is static"
361-
362362
expect_lint(paste("x", pipe, "grepl(pattern = 'a')"), lint_msg, linter)
363363
expect_no_lint(paste("x", pipe, "grepl(pattern = '^a')"), linter)
364364
expect_no_lint(paste("x", pipe, "grepl(pattern = 'a', fixed = TRUE)"), linter)
@@ -377,3 +377,14 @@ local({
377377
.test_name = names(pipes)
378378
)
379379
})
380+
381+
test_that("pipe-aware lint logic survives adversarial comments", {
382+
expect_lint(
383+
trim_some("
384+
x %>% grepl(pattern = # comment
385+
'a')
386+
"),
387+
"This regular expression is static",
388+
fixed_regex_linter()
389+
)
390+
})

tests/testthat/test-object_length_linter.R

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,4 +104,14 @@ test_that("literals in assign() and setGeneric() are checked", {
104104
expect_lint("assign(x = 'badBadBadBadName', 2, env)", lint_msg, linter)
105105
expect_lint("assign(envir = 'good_env_name', 'badBadBadBadName', 2)", lint_msg, linter)
106106
expect_lint("assign(envir = 'good_env_name', x = 'badBadBadBadName', 2)", lint_msg, linter)
107+
108+
# adversarial comments
109+
expect_lint(
110+
trim_some("
111+
assign(envir = # comment
112+
'good_env_name', 'badBadBadBadName', 2)
113+
"),
114+
lint_msg,
115+
linter
116+
)
107117
})

0 commit comments

Comments
 (0)