Skip to content

Commit 3a62b86

Browse files
New ifelse_censor_linter (#1007)
* New ifelse_censor_linter * customize lint to whether pmin/pmax is needed * customize to the actual function as well * note about re-using constant for future refactorers Co-authored-by: AshesITR <alexander.rosenstock@web.de>
1 parent 5aa88f9 commit 3a62b86

11 files changed

+156
-0
lines changed

DESCRIPTION

+1
Original file line numberDiff line numberDiff line change
@@ -86,6 +86,7 @@ Collate:
8686
'get_source_expressions.R'
8787
'ids_with_token.R'
8888
'if_else_match_braces_linter.R'
89+
'ifelse_censor_linter.R'
8990
'implicit_integer_linter.R'
9091
'infix_spaces_linter.R'
9192
'line_length_linter.R'

NAMESPACE

+1
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ export(function_left_parentheses_linter)
5252
export(get_source_expressions)
5353
export(ids_with_token)
5454
export(if_else_match_braces_linter)
55+
export(ifelse_censor_linter)
5556
export(implicit_integer_linter)
5657
export(infix_spaces_linter)
5758
export(line_length_linter)

NEWS.md

+1
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@ function calls. (#850, #851, @renkun-ken)
120120
* `unreachable_code_linter()` Prevent code after `return()` and `stop()` statements that will never be reached
121121
* `regex_subset_linter()` Require usage of `grep(ptn, x, value = TRUE)` over `x[grep(ptn, x)]` and similar
122122
* `consecutive_stopifnot_linter()` Require consecutive calls to `stopifnot()` to be unified into one
123+
* `ifelse_censor_linter()` Require usage of `pmax()` / `pmin()` where appropriate, e.g. `ifelse(x > y, x, y)` is `pmax(x, y)`
123124
* `system_file_linter()` Require file paths to be constructed by `system.file()` instead of calling `file.path()` directly
124125
* `assignment_linter()` now lints right assignment (`->` and `->>`) and gains two arguments. `allow_cascading_assign` (`TRUE` by default) toggles whether to lint `<<-` and `->>`; `allow_right_assign` toggles whether to lint `->` and `->>` (#915, @michaelchirico)
125126
* `infix_spaces_linter()` gains argument `exclude_operators` to disable lints on selected infix operators. By default, all "low-precedence" operators throw lints; see `?infix_spaces_linter` for an enumeration of these. (#914 @michaelchirico)

R/ifelse_censor_linter.R

+57
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
#' Block usage of ifelse where pmin or pmax is more appropriate
2+
#'
3+
#' `ifelse(x > M, M, x)` is the same as `pmin(x, M)`, but harder
4+
#' to read and requires several passes over the vector.
5+
#'
6+
#' The same goes for other similar ways to censor a vector, e.g.
7+
#' `ifelse(x <= M, x, M)` is `pmin(x, M)`,
8+
#' `ifelse(x < m, m, x)` is `pmax(x, m)`, and
9+
#' `ifelse(x >= m, x, m)` is `pmax(x, m)`.
10+
#'
11+
#' @evalRd rd_tags("ifelse_censor_linter")
12+
#' @seealso [linters] for a complete list of linters available in lintr.
13+
#' @export
14+
ifelse_censor_linter <- function() {
15+
Linter(function(source_file) {
16+
if (length(source_file$xml_parsed_content) == 0L) {
17+
return(list())
18+
}
19+
20+
xml <- source_file$xml_parsed_content
21+
22+
xpath <- glue::glue("//expr[
23+
expr[SYMBOL_FUNCTION_CALL[ {xp_text_in_table(ifelse_funs)} ]]
24+
and expr[2][
25+
(LT or GT or LE or GE)
26+
and expr[1] = following-sibling::expr
27+
and expr[2] = following-sibling::expr
28+
]
29+
]")
30+
bad_expr <- xml2::xml_find_all(xml, xpath)
31+
32+
return(lapply(
33+
bad_expr,
34+
xml_nodes_to_lint,
35+
source_file = source_file,
36+
lint_message = function(expr) {
37+
matched_call <- xml2::xml_text(xml2::xml_find_first(expr, "expr/SYMBOL_FUNCTION_CALL"))
38+
op <- xml2::xml_text(xml2::xml_find_first(expr, "expr[2]/*[2]"))
39+
match_first <- !is.na(xml2::xml_find_first(expr, "expr[2][expr[1] = following-sibling::expr[1]]"))
40+
if (op %in% c("<", "<=")) {
41+
if (match_first) {
42+
sprintf("pmin(x, y) is preferable to %s(x %s y, x, y).", matched_call, op)
43+
} else {
44+
sprintf("pmax(x, y) is preferable to %s(x %s y, y, x).", matched_call, op)
45+
}
46+
} else {
47+
if (match_first) {
48+
sprintf("pmax(x, y) is preferable to %s(x %s y, x, y).", matched_call, op)
49+
} else {
50+
sprintf("pmin(x, y) is preferable to %s(x %s y, y, x).", matched_call, op)
51+
}
52+
}
53+
},
54+
type = "warning"
55+
))
56+
})
57+
}

R/nested_ifelse_linter.R

+1
Original file line numberDiff line numberDiff line change
@@ -46,4 +46,5 @@ nested_ifelse_linter <- function() {
4646
}
4747

4848
# functions equivalent to base::ifelse() for linting purposes
49+
# NB: this is re-used elsewhere, e.g. in ifelse_censor_linter
4950
ifelse_funs <- c("ifelse", "if_else", "fifelse")

inst/lintr/linters.csv

+1
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ extraction_operator_linter,style best_practices
2828
function_brace_linter,default style readability
2929
function_left_parentheses_linter,style readability default
3030
if_else_match_braces_linter,default style readability
31+
ifelse_censor_linter,best_practices efficiency
3132
implicit_integer_linter,style consistency best_practices
3233
infix_spaces_linter,style readability default
3334
line_length_linter,style readability default configurable

man/best_practices_linters.Rd

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/efficiency_linters.Rd

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/ifelse_censor_linter.Rd

+24
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/linters.Rd

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
+67
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,67 @@
1+
test_that("ifelse_censor_linter skips allowed usages", {
2+
expect_lint("ifelse(x > 2, x, y)", NULL, ifelse_censor_linter())
3+
expect_lint("ifelse(x > 2, x, y)", NULL, ifelse_censor_linter())
4+
})
5+
6+
test_that("ifelse_censor_linter blocks simple disallowed usages", {
7+
expect_lint(
8+
"ifelse(x < 0, 0, x)",
9+
rex::rex("pmax(x, y) is preferable to ifelse(x < y, y, x)"),
10+
ifelse_censor_linter()
11+
)
12+
# other equivalents to base::ifelse()
13+
expect_lint(
14+
"if_else(x < 0, 0, x)",
15+
rex::rex("pmax(x, y) is preferable to if_else(x < y, y, x)"),
16+
ifelse_censor_linter()
17+
)
18+
expect_lint(
19+
"fifelse(x < 0, 0, x)",
20+
rex::rex("pmax(x, y) is preferable to fifelse(x < y, y, x)"),
21+
ifelse_censor_linter()
22+
)
23+
24+
# other equivalents for censoring
25+
expect_lint(
26+
"ifelse(x <= 0, 0, x)",
27+
rex::rex("pmax(x, y) is preferable to ifelse(x <= y, y, x)"),
28+
ifelse_censor_linter()
29+
)
30+
expect_lint(
31+
"ifelse(x > 0, x, 0)",
32+
rex::rex("pmax(x, y) is preferable to ifelse(x > y, x, y)"),
33+
ifelse_censor_linter()
34+
)
35+
expect_lint(
36+
"ifelse(x >= 0, x, 0)",
37+
rex::rex("pmax(x, y) is preferable to ifelse(x >= y, x, y)"),
38+
ifelse_censor_linter()
39+
)
40+
41+
# pairwise min/max (similar to censoring)
42+
expect_lint(
43+
"ifelse(x < y, x, y)",
44+
rex::rex("pmin(x, y) is preferable to ifelse(x < y, x, y)"),
45+
ifelse_censor_linter()
46+
)
47+
expect_lint(
48+
"ifelse(x >= y, y, x)",
49+
rex::rex("pmin(x, y) is preferable to ifelse(x >= y, y, x)"),
50+
ifelse_censor_linter()
51+
)
52+
53+
# more complicated expression still matches
54+
lines <- trim_some("
55+
ifelse(2 + p + 104 + 1 > ncols,
56+
ncols, 2 + p + 104 + 1
57+
)
58+
")
59+
expect_lint(
60+
lines,
61+
rex::rex("pmin(x, y) is preferable to ifelse(x > y, y, x)"),
62+
ifelse_censor_linter()
63+
)
64+
})
65+
66+
# TODO(michaelchirico): how easy would it be to strip parens when considering lint?
67+
# e.g. ifelse(x < (kMaxIndex - 1), x, kMaxIndex - 1)

0 commit comments

Comments
 (0)