Skip to content

Commit d6bacad

Browse files
New nested_ifelse_linter (#996)
* New nested_ifelse_linter * wording
1 parent 856f1dd commit d6bacad

File tree

10 files changed

+148
-3
lines changed

10 files changed

+148
-3
lines changed

DESCRIPTION

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,7 @@ Collate:
9292
'missing_package_linter.R'
9393
'namespace.R'
9494
'namespace_linter.R'
95+
'nested_ifelse_linter.R'
9596
'no_tab_linter.R'
9697
'numeric_leading_zero_linter.R'
9798
'object_name_linters.R'

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ export(lint_package)
5656
export(missing_argument_linter)
5757
export(missing_package_linter)
5858
export(namespace_linter)
59+
export(nested_ifelse_linter)
5960
export(no_tab_linter)
6061
export(nonportable_path_linter)
6162
export(numeric_leading_zero_linter)

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -102,6 +102,7 @@ function calls. (#850, #851, @renkun-ken)
102102
* `any_is_na_linter()` Require usage of `anyNA(x)` over `any(is.na(x))`
103103
* `outer_negation_linter()` Require usage of `!any(x)` over `all(!x)` and `!all(x)` over `any(!x)`
104104
* `numeric_leading_zero_linter()` Require a leading `0` in fractional numeric constants, e.g. `0.1` instead of `.1`
105+
* `nested_ifelse_linter()` Prevent nested calls to `ifelse()` like `ifelse(A, x, ifelse(B, y, z))`, and similar
105106
* `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)
106107
* `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)
107108
* `infix_spaces_linter()` now throws a lint on `a~b` and `function(a=1) {}` (#930, @michaelchirico)

R/nested_ifelse_linter.R

Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,49 @@
1+
#' Block usage of nested ifelse() calls
2+
#'
3+
#' Calling `ifelse` in nested calls is problematic for two main reasons:
4+
#' 1. It can be hard to read -- mapping the code to the expected output
5+
#' for such code can be a messy task/require a lot of mental bandwidth,
6+
#' especially for code that nests more than once
7+
#' 2. It is inefficient -- `ifelse` can evaluate _all_ of its arguments at
8+
#' both yes and no (see https://stackoverflow.com/q/16275149); this issue
9+
#' is exacerbated for nested calls
10+
#'
11+
#' Users can instead rely on a more readable alternative modeled after SQL
12+
#' CASE WHEN statements, such as `data.table::fcase` or `dplyr::case_when`,
13+
#' or use a look-up-and-merge approach (build a mapping table between values
14+
#' and outputs and merge this to the input).
15+
#'
16+
#' @evalRd rd_tags("nested_ifelse_linter")
17+
#' @seealso [linters] for a complete list of linters available in lintr.
18+
#' @export
19+
nested_ifelse_linter <- function() {
20+
Linter(function(source_file) {
21+
if (length(source_file$parsed_content) == 0L) {
22+
return(list())
23+
}
24+
25+
xml <- source_file$xml_parsed_content
26+
27+
xpath <- glue::glue("
28+
//expr[expr[SYMBOL_FUNCTION_CALL[ {xp_text_in_table(ifelse_funs)} ]]]
29+
/expr[expr[SYMBOL_FUNCTION_CALL[ {xp_text_in_table(ifelse_funs)} ]]]
30+
")
31+
32+
bad_expr <- xml2::xml_find_all(xml, xpath)
33+
34+
return(lapply(
35+
bad_expr,
36+
xml_nodes_to_lint,
37+
source_file = source_file,
38+
lint_message = function(expr) {
39+
matched_call <- xml2::xml_text(xml2::xml_find_first(expr, "expr/SYMBOL_FUNCTION_CALL"))
40+
lint_message <- sprintf("Don't use nested %s() calls;", matched_call)
41+
paste(lint_message, "instead, try (1) data.table::fcase; (2) dplyr::case_when; or (3) using a lookup table.")
42+
},
43+
type = "warning"
44+
))
45+
})
46+
}
47+
48+
# functions equivalent to base::ifelse() for linting purposes
49+
ifelse_funs <- c("ifelse", "if_else", "fifelse")

inst/lintr/linters.csv

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ line_length_linter,style readability default configurable
2929
missing_argument_linter,correctness common_mistakes configurable
3030
missing_package_linter,robustness common_mistakes
3131
namespace_linter,correctness robustness configurable
32+
nested_ifelse_linter,efficiency readability
3233
no_tab_linter,style consistency default
3334
nonportable_path_linter,robustness best_practices configurable
3435
numeric_leading_zero_linter,style consistency readability

man/efficiency_linters.Rd

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

man/linters.Rd

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

man/nested_ifelse_linter.Rd

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

man/readability_linters.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Lines changed: 58 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,58 @@
1+
test_that("nested_ifelse_linter skips allowed usages", {
2+
expect_lint("if (TRUE) 1 else 2", NULL, nested_ifelse_linter())
3+
4+
expect_lint("ifelse(runif(10) > .2, 4, 6)", NULL, nested_ifelse_linter())
5+
6+
# don't block suggested alternatives
7+
expect_lint("fcase(l1, v1, l2, v2)", NULL, nested_ifelse_linter())
8+
expect_lint("case_when(l1 ~ v1, l2 ~ v2)", NULL, nested_ifelse_linter())
9+
})
10+
11+
test_that("nested_ifelse_linter blocks simple disallowed usages", {
12+
expect_lint(
13+
"ifelse(l1, v1, ifelse(l2, v2, v3))",
14+
rex::rex("Don't use nested ifelse() calls"),
15+
nested_ifelse_linter()
16+
)
17+
18+
expect_lint(
19+
"ifelse(l1, ifelse(l2, v1, v2), v3)",
20+
rex::rex("Don't use nested ifelse() calls"),
21+
nested_ifelse_linter()
22+
)
23+
})
24+
25+
test_that("nested_ifelse_linter also catches dplyr::if_else", {
26+
expect_lint(
27+
"if_else(l1, v1, if_else(l2, v2, v3))",
28+
rex::rex("Don't use nested if_else() calls"),
29+
nested_ifelse_linter()
30+
)
31+
32+
expect_lint(
33+
"dplyr::if_else(l1, dplyr::if_else(l2, v1, v2), v3)",
34+
rex::rex("Don't use nested if_else() calls"),
35+
nested_ifelse_linter()
36+
)
37+
})
38+
39+
test_that("nested_ifelse_linter also catches data.table::fifelse", {
40+
expect_lint(
41+
"fifelse(l1, v1, fifelse(l2, v2, v3))",
42+
rex::rex("Don't use nested fifelse() calls"),
43+
nested_ifelse_linter()
44+
)
45+
46+
expect_lint(
47+
"data.table::fifelse(l1, v1, data.table::fifelse(l2, v2, v3))",
48+
rex::rex("Don't use nested fifelse() calls"),
49+
nested_ifelse_linter()
50+
)
51+
52+
# not sure why anyone would do this, but the readability still argument holds
53+
expect_lint(
54+
"data.table::fifelse(l1, dplyr::if_else(l2, v1, v2), v3)",
55+
rex::rex("Don't use nested if_else() calls"),
56+
nested_ifelse_linter()
57+
)
58+
})

0 commit comments

Comments
 (0)