Skip to content

Commit 35f3344

Browse files
authored
Allow to opt out of linting filter() in conjunct_test_linter (#2110)
* opt out of linting filter() in conjunct_test_linter fixes #2108 * Use tidyverse style in examples * Add test for conjunct_test_linter(allow_filter = TRUE) * Add NEWS bullet * Merge NEWS items * Write examples on fewer lines
1 parent 02732a2 commit 35f3344

File tree

4 files changed

+62
-20
lines changed

4 files changed

+62
-20
lines changed

NEWS.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@
2727
+ `yoda_test_linter()`
2828
* `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico).
2929
* `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico).
30-
* `conjunct_test_linter()` also lints usage like `dplyr::filter(x, A & B)` in favor of using `dplyr::filter(x, A, B)` (part of #884, @MichaelChirico).
30+
* `conjunct_test_linter()` also lints usage like `dplyr::filter(x, A & B)` in favor of using `dplyr::filter(x, A, B)` unless `allow_filter = TRUE` (part of #884, @MichaelChirico; #2110, @salim-b).
3131
* `sort_linter()` checks for code like `x == sort(x)` which is better served by using the function `is.unsorted()` (part of #884, @MichaelChirico).
3232
* `paste_linter()` gains detection for file paths that are better constructed with `file.path()`, e.g. `paste0(dir, "/", file)` would be better as `file.path(dir, file)` (part of #884, @MichaelChirico).
3333
* `seq_linter()` recommends `rev()` in the lint message for lints like `nrow(x):1` (#1542, @MichaelChirico).

R/conjunct_test_linter.R

Lines changed: 30 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -7,13 +7,14 @@
77
#'
88
#' Similar reasoning applies to `&&` usage inside [stopifnot()] and `assertthat::assert_that()` calls.
99
#'
10-
#' Relatedly, `dplyr::filter(DF, A & B)` is the same as `dplyr::filter(DF, A, B)`, but the
11-
#' latter will be more readable / easier to format for long conditions. Note that this linter
12-
#' assumes usages of `filter()` are `dplyr::filter()`; if you're using another function named `filter()`,
13-
#' e.g. [stats::filter()], please namespace-qualify it to avoid false positives.
10+
#' Relatedly, `dplyr::filter(DF, A & B)` is the same as `dplyr::filter(DF, A, B)`, but the latter will be more readable
11+
#' / easier to format for long conditions. Note that this linter assumes usages of `filter()` are `dplyr::filter()`;
12+
#' if you're using another function named `filter()`, e.g. [stats::filter()], please namespace-qualify it to avoid
13+
#' false positives. You can omit linting `filter()` expressions altogether via `allow_filter = TRUE`.
1414
#'
1515
#' @param allow_named_stopifnot Logical, `TRUE` by default. If `FALSE`, "named" calls to `stopifnot()`,
1616
#' available since R 4.0.0 to provide helpful messages for test failures, are also linted.
17+
#' @param allow_filter Logical, `FALSE` by default. If `TRUE`, `filter()` expressions are not linted.
1718
#'
1819
#' @examples
1920
#' # will produce lints
@@ -32,6 +33,11 @@
3233
#' linters = conjunct_test_linter(allow_named_stopifnot = FALSE)
3334
#' )
3435
#'
36+
#' lint(
37+
#' text = "dplyr::filter(mtcars, mpg > 20 & vs == 0)",
38+
#' linters = conjunct_test_linter()
39+
#' )
40+
#'
3541
#' # okay
3642
#' lint(
3743
#' text = "expect_true(x || (y && z))",
@@ -43,10 +49,16 @@
4349
#' linters = conjunct_test_linter(allow_named_stopifnot = TRUE)
4450
#' )
4551
#'
52+
#' lint(
53+
#' text = "dplyr::filter(mtcars, mpg > 20 & vs == 0)",
54+
#' linters = conjunct_test_linter(allow_filter = TRUE)
55+
#' )
56+
#'
4657
#' @evalRd rd_tags("conjunct_test_linter")
4758
#' @seealso [linters] for a complete list of linters available in lintr.
4859
#' @export
49-
conjunct_test_linter <- function(allow_named_stopifnot = TRUE) {
60+
conjunct_test_linter <- function(allow_named_stopifnot = TRUE,
61+
allow_filter = FALSE) {
5062
expect_true_assert_that_xpath <- "
5163
//SYMBOL_FUNCTION_CALL[text() = 'expect_true' or text() = 'assert_that']
5264
/parent::expr
@@ -103,22 +115,26 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE) {
103115
sprintf(as.character(replacement_fmt), matched_fun),
104116
"The latter will produce better error messages in the case of failure."
105117
)
106-
test_lints <- xml_nodes_to_lints(
118+
lints <- xml_nodes_to_lints(
107119
test_expr,
108120
source_expression = source_expression,
109121
lint_message = lint_message,
110122
type = "warning"
111123
)
112124

113-
filter_expr <- xml_find_all(xml, filter_xpath)
125+
if (!allow_filter) {
126+
filter_expr <- xml_find_all(xml, filter_xpath)
114127

115-
filter_lints <- xml_nodes_to_lints(
116-
filter_expr,
117-
source_expression = source_expression,
118-
lint_message = "Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B).",
119-
type = "warning"
120-
)
128+
filter_lints <- xml_nodes_to_lints(
129+
filter_expr,
130+
source_expression = source_expression,
131+
lint_message = "Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B).",
132+
type = "warning"
133+
)
134+
135+
lints <- c(lints, filter_lints)
136+
}
121137

122-
c(test_lints, filter_lints)
138+
lints
123139
})
124140
}

man/conjunct_test_linter.Rd

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

tests/testthat/test-conjunct_test_linter.R

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -131,6 +131,14 @@ test_that("conjunct_test_linter blocks simple disallowed usages", {
131131
expect_lint("DF %>% dplyr::filter(A & B)", lint_msg, linter)
132132
})
133133

134+
test_that("conjunct_test_linter respects its allow_filter argument", {
135+
linter <- conjunct_test_linter(allow_filter = TRUE)
136+
137+
expect_lint("dplyr::filter(DF, A & B)", NULL, linter)
138+
expect_lint("dplyr::filter(DF, A & B & C)", NULL, linter)
139+
expect_lint("DF %>% dplyr::filter(A & B)", NULL, linter)
140+
})
141+
134142
test_that("filter() is assumed to be dplyr::filter() by default, unless o/w specified", {
135143
linter <- conjunct_test_linter()
136144

0 commit comments

Comments
 (0)