Skip to content

Commit 9c7db92

Browse files
authored
Merge f5e633d into 4b59aac
2 parents 4b59aac + f5e633d commit 9c7db92

File tree

75 files changed

+348
-118
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

75 files changed

+348
-118
lines changed

NEWS.md

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,14 +38,15 @@
3838
* `unnecessary_lambda_linter` is extended to encourage vectorized comparisons where possible, e.g. `sapply(x, sum) > 0` instead of `sapply(x, function(x) sum(x) > 0)` (part of #884, @MichaelChirico). Toggle this behavior with argument `allow_comparison`.
3939
* `backport_linter()` is slightly faster by moving expensive computations outside the linting function (#2339, #2348, @AshesITR and @MichaelChirico).
4040
* `Linter()` has a new argument `linter_level` (default `NA`). This is used by `lint()` to more efficiently check for expression levels than the idiom `if (!is_lint_level(...)) { return(list()) }` (#2351, @AshesITR).
41+
* `Linter()` has a new argument `supports_exprlist` (default `FALSE`). This is used by `lint()` to more efficiently run expression-level linters if they support linting multiple expressions in parallel. Most linters are cacheable on the expression level, but support running for many expressions in parallel. Exprlist linting mode aggregates expressions before calling the linter and causes linting to be roughly 2x faster (#2449, @AshesITR).
4142
* `string_boundary_linter()` recognizes regular expression calls like `grepl("^abc$", x)` that can be replaced by using `==` instead (#1613, @MichaelChirico).
4243
* `unreachable_code_linter()` has an argument `allow_comment_regex` for customizing which "terminal" comments to exclude (#2327, @MichaelChirico). `# nolint end` comments are always excluded, as are {covr} exclusions (e.g. `# nocov end`) by default.
4344
* `format()` and `print()` methods for `lint` and `lints` classes get a new option `width` to control the printing width of lint messages (#1884, @MichaelChirico). The default is controlled by a new option `lintr.format_width`; if unset, no wrapping occurs (matching earlier behavior).
4445
* `implicit_assignment_linter()` gets a custom message for the case of using `(` to induce printing like `(x <- foo())`; use an explicit call to `print()` for clarity (#2257, @MichaelChirico).
4546
* New function node caching for big efficiency gains to most linters (e.g. overall `lint_package()` improvement of 14-27% and core linting improvement up to 30%; #2357, @AshesITR). Most linters are written around function usage, and XPath performance searching for many functions is poor. The new `xml_find_function_calls()` entry in the `get_source_expressions()` output caches all function call nodes instead. See the vignette on creating linters for more details on how to use it.
4647
* `todo_comment_linter()` has a new argument `except_regex` for setting _valid_ TODO comments, e.g. for forcing TODO comments to be linked to GitHub issues like `TODO(#154)` (#2047, @MichaelChirico).
4748
* `vector_logic_linter()` is extended to recognize incorrect usage of scalar operators `&&` and `||` inside subsetting expressions like `dplyr::filter(x, A && B)` (#2166, @MichaelChirico).
48-
* `any_is_na_linter()` is extended to catch the unusual usage `NA %in% x` (#2113, @MichaelChirico).
49+
* `any_is_na_linter()` is extended to catch the unusual usage `NA %in% x` (#2113, @MichaelChirico).
4950

5051
### New linters
5152

R/T_and_F_symbol_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ T_and_F_symbol_linter <- function() { # nolint: object_name.
4444

4545
replacement_map <- c(T = "TRUE", F = "FALSE")
4646

47-
Linter(linter_level = "expression", function(source_expression) {
47+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4848
xml <- source_expression$xml_parsed_content
4949

5050
bad_usage <- xml_find_all(xml, usage_xpath)

R/any_duplicated_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ any_duplicated_linter <- function() {
8484

8585
uses_nrow_xpath <- "./parent::expr/expr/expr[1]/SYMBOL_FUNCTION_CALL[text() = 'nrow']"
8686

87-
Linter(linter_level = "expression", function(source_expression) {
87+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8888
xml <- source_expression$xml_parsed_content
8989
xml_calls <- source_expression$xml_find_function_calls("any")
9090

R/any_is_na_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ any_is_na_linter <- function() {
4747

4848
in_xpath <- "//SPECIAL[text() = '%in%']/preceding-sibling::expr[NUM_CONST[starts-with(text(), 'NA')]]"
4949

50-
Linter(linter_level = "expression", function(source_expression) {
50+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
5151
xml <- source_expression$xml_parsed_content
5252
xml_calls <- source_expression$xml_find_function_calls("any")
5353

R/assignment_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ assignment_linter <- function(allow_cascading_assign = TRUE,
9999
if (!allow_pipe_assign) "//SPECIAL[text() = '%<>%']"
100100
))
101101

102-
Linter(linter_level = "expression", function(source_expression) {
102+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
103103
xml <- source_expression$xml_parsed_content
104104

105105
bad_expr <- xml_find_all(xml, xpath)

R/backport_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ backport_linter <- function(r_version = getRversion(), except = character()) {
4545
backport_index <- rep(names(backport_blacklist), times = lengths(backport_blacklist))
4646
names(backport_index) <- unlist(backport_blacklist)
4747

48-
Linter(linter_level = "expression", function(source_expression) {
48+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4949
xml <- source_expression$xml_parsed_content
5050

5151
used_symbols <- xml_find_all(xml, "//SYMBOL")

R/boolean_arithmetic_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ boolean_arithmetic_linter <- function() {
5252
]
5353
")
5454

55-
Linter(linter_level = "expression", function(source_expression) {
55+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
5656
length_calls <- source_expression$xml_find_function_calls(c("which", "grep"))
5757
sum_calls <- source_expression$xml_find_function_calls("sum")
5858
any_expr <- c(

R/brace_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ brace_linter <- function(allow_single_line = FALSE) {
146146
]
147147
"
148148

149-
Linter(linter_level = "expression", function(source_expression) {
149+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
150150
xml <- source_expression$xml_parsed_content
151151

152152
lints <- list()

R/class_equals_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ class_equals_linter <- function() {
4343
]
4444
"
4545

46-
Linter(linter_level = "expression", function(source_expression) {
46+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4747
xml_calls <- source_expression$xml_find_function_calls("class")
4848
bad_expr <- xml_find_all(xml_calls, xpath)
4949

R/commas_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ commas_linter <- function(allow_trailing = FALSE) {
7777
"]"
7878
)
7979

80-
Linter(linter_level = "expression", function(source_expression) {
80+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8181
xml <- source_expression$xml_parsed_content
8282

8383
before_lints <- xml_nodes_to_lints(

R/comparison_negation_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ comparison_negation_linter <- function() {
6060
]
6161
")
6262

63-
Linter(linter_level = "expression", function(source_expression) {
63+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6464
xml <- source_expression$xml_parsed_content
6565

6666
bad_expr <- xml_find_all(xml, xpath)

R/condition_call_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ condition_call_linter <- function(display_call = FALSE) {
7979

8080
xpath <- glue::glue("parent::expr[{call_cond}]/parent::expr")
8181

82-
Linter(linter_level = "expression", function(source_expression) {
82+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8383
xml_calls <- source_expression$xml_find_function_calls(c("stop", "warning"))
8484
bad_expr <- xml_find_all(xml_calls, xpath)
8585

R/condition_message_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ condition_message_linter <- function() {
5555
/parent::expr
5656
")
5757

58-
Linter(linter_level = "expression", function(source_expression) {
58+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
5959
xml_calls <- source_expression$xml_find_function_calls(translators)
6060
bad_expr <- xml_find_all(xml_calls, xpath)
6161
sep_value <- get_r_string(bad_expr, xpath = "./expr/SYMBOL_SUB[text() = 'sep']/following-sibling::expr/STR_CONST")

R/equals_na_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ equals_na_linter <- function() {
4646
/parent::expr
4747
")
4848

49-
Linter(linter_level = "expression", function(source_expression) {
49+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
5050
xml <- source_expression$xml_parsed_content
5151

5252
bad_expr <- xml_find_all(xml, xpath)

R/expect_comparison_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ expect_comparison_linter <- function() {
6262
`==` = "expect_identical"
6363
)
6464

65-
Linter(linter_level = "expression", function(source_expression) {
65+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6666
xml_calls <- source_expression$xml_find_function_calls("expect_true")
6767
bad_expr <- xml_find_all(xml_calls, xpath)
6868

R/expect_identical_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ expect_identical_linter <- function() {
7777
/following-sibling::expr[1][expr[1]/SYMBOL_FUNCTION_CALL[text() = 'identical']]
7878
/parent::expr
7979
"
80-
Linter(linter_level = "expression", function(source_expression) {
80+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8181
expect_equal_calls <- source_expression$xml_find_function_calls("expect_equal")
8282
expect_true_calls <- source_expression$xml_find_function_calls("expect_true")
8383
bad_expr <- c(

R/expect_length_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ expect_length_linter <- function() {
3131
/parent::expr[not(SYMBOL_SUB[text() = 'info' or contains(text(), 'label')])]
3232
")
3333

34-
Linter(linter_level = "expression", function(source_expression) {
34+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
3535
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
3636
bad_expr <- xml_find_all(xml_calls, xpath)
3737

R/expect_named_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ expect_named_linter <- function() {
4040
/parent::expr
4141
"
4242

43-
Linter(linter_level = "expression", function(source_expression) {
43+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4444
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
4545
bad_expr <- xml_find_all(xml_calls, xpath)
4646
matched_function <- xp_call_name(bad_expr)

R/expect_null_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ expect_null_linter <- function() {
5050
/parent::expr
5151
"
5252

53-
Linter(linter_level = "expression", function(source_expression) {
53+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
5454
expect_equal_identical_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
5555
expect_true_calls <- source_expression$xml_find_function_calls("expect_true")
5656

R/expect_s3_class_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ expect_s3_class_linter <- function() {
6666
/parent::expr[not(SYMBOL_SUB[text() = 'info' or text() = 'label'])]
6767
")
6868

69-
Linter(linter_level = "expression", function(source_expression) {
69+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
7070
expect_equal_identical_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
7171
expect_true_calls <- source_expression$xml_find_function_calls("expect_true")
7272

R/expect_s4_class_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ expect_s4_class_linter <- function() {
3131
/parent::expr[not(SYMBOL_SUB[text() = 'info' or text() = 'label'])]
3232
"
3333

34-
Linter(linter_level = "expression", function(source_expression) {
34+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
3535
# TODO(#2423): also catch expect_{equal,identical}(methods::is(x), k).
3636
# this seems empirically rare, but didn't check many S4-heavy packages.
3737

R/expect_true_false_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ expect_true_false_linter <- function() {
3838
/parent::expr
3939
"
4040

41-
Linter(linter_level = "expression", function(source_expression) {
41+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4242
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
4343
bad_expr <- xml_find_all(xml_calls, xpath)
4444

R/expect_type_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ expect_type_linter <- function() {
5656
/parent::expr[not(SYMBOL_SUB[text() = 'info' or text() = 'label'])]
5757
")
5858

59-
Linter(linter_level = "expression", function(source_expression) {
59+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6060
expect_equal_identical_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
6161
expect_true_calls <- source_expression$xml_find_function_calls("expect_true")
6262
bad_expr <- combine_nodesets(

R/fixed_regex_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {
138138
]
139139
")
140140

141-
Linter(linter_level = "expression", function(source_expression) {
141+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
142142
pos_1_calls <- source_expression$xml_find_function_calls(pos_1_regex_funs)
143143
pos_2_calls <- source_expression$xml_find_function_calls(pos_2_regex_funs)
144144
patterns <- combine_nodesets(

R/function_argument_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ function_argument_linter <- function() {
5959
text() = following-sibling::expr[last()]//expr[expr/SYMBOL_FUNCTION_CALL[text() = 'missing']]/expr[2]/SYMBOL/text()
6060
"
6161

62-
Linter(linter_level = "expression", function(source_expression) {
62+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6363
xml <- source_expression$xml_parsed_content
6464

6565
bad_expr <- xml_find_all(xml, xpath)

R/function_left_parentheses_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ function_left_parentheses_linter <- function() { # nolint: object_length.
5757
and @col2 != parent::expr/following-sibling::OP-LEFT-PAREN/@col1 - 1
5858
]"
5959

60-
Linter(linter_level = "expression", function(source_expression) {
60+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6161
xml <- source_expression$xml_parsed_content
6262

6363
bad_line_fun_exprs <- xml_find_all(xml, bad_line_fun_xpath)

R/if_not_else_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ if_not_else_linter <- function(exceptions = c("is.null", "is.na", "missing")) {
8282
]]
8383
")
8484

85-
Linter(linter_level = "expression", function(source_expression) {
85+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8686
xml <- source_expression$xml_parsed_content
8787
ifelse_calls <- source_expression$xml_find_function_calls(ifelse_funs)
8888

R/if_switch_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,7 @@ if_switch_linter <- function() {
6161
]
6262
")
6363

64-
Linter(linter_level = "expression", function(source_expression) {
64+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
6565
xml <- source_expression$xml_parsed_content
6666

6767
bad_expr <- xml_find_all(xml, xpath)

R/ifelse_censor_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ ifelse_censor_linter <- function() {
4545
/parent::expr
4646
")
4747

48-
Linter(linter_level = "expression", function(source_expression) {
48+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
4949
ifelse_calls <- source_expression$xml_find_function_calls(ifelse_funs)
5050
bad_expr <- xml_find_all(ifelse_calls, xpath)
5151

R/infix_spaces_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ infix_spaces_linter <- function(exclude_operators = NULL, allow_multiple_spaces
105105
)
106106
]")
107107

108-
Linter(linter_level = "expression", function(source_expression) {
108+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
109109
xml <- source_expression$xml_parsed_content
110110

111111
bad_expr <- xml_find_all(xml, xpath)

R/inner_combine_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ inner_combine_linter <- function() {
8282
/parent::expr
8383
")
8484

85-
Linter(linter_level = "expression", function(source_expression) {
85+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
8686
xml_calls <- source_expression$xml_find_function_calls("c")
8787
bad_expr <- xml_find_all(xml_calls, xpath)
8888

R/is_lint_level.R

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,3 +43,16 @@ is_linter_level <- function(linter, level = c("expression", "file")) {
4343
level <- match.arg(level)
4444
identical(linter_level, level)
4545
}
46+
47+
#' Determine whether an expression-level linter can handle multiple expressions at once
48+
#'
49+
#' Used by [lint()] to efficiently batch calls to expression-level linters.
50+
#'
51+
#' @param linter A linter.
52+
#'
53+
#' @keywords internal
54+
#' @noRd
55+
linter_supports_exprlist <- function(linter) {
56+
linter_exprlist <- attr(linter, "linter_exprlist", exact = TRUE)
57+
isTRUE(linter_exprlist)
58+
}

R/is_numeric_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ is_numeric_linter <- function() {
6969
/parent::expr
7070
"
7171

72-
Linter(linter_level = "expression", function(source_expression) {
72+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
7373
xml <- source_expression$xml_parsed_content
7474

7575
or_expr <- xml_find_all(xml, or_xpath)

R/keyword_quote_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,7 @@ keyword_quote_linter <- function() {
9393
no_quote_msg <- "Use backticks to create non-syntactic names, not quotes."
9494
clarification <- "i.e., if the name is not a valid R symbol (see ?make.names)."
9595

96-
Linter(linter_level = "expression", function(source_expression) {
96+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
9797
xml <- source_expression$xml_parsed_content
9898
xml_calls <- source_expression$xml_find_function_calls(NULL)
9999

R/length_test_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ length_test_linter <- function() {
2626
/parent::expr
2727
")
2828

29-
Linter(linter_level = "expression", function(source_expression) {
29+
Linter(linter_level = "expression", supports_exprlist = TRUE, function(source_expression) {
3030
xml_calls <- source_expression$xml_find_function_calls("length")
3131
bad_expr <- xml_find_all(xml_calls, xpath)
3232

0 commit comments

Comments
 (0)