-
Notifications
You must be signed in to change notification settings - Fork 186
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
3e7bb47
commit ef1aa15
Showing
11 changed files
with
192 additions
and
3 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,83 @@ | ||
#' Require usage of switch() over repeated if/else blocks | ||
#' | ||
#' [switch()] statements in R are used to delegate behavior based | ||
#' on the value of some input scalar string, e.g. | ||
#' `switch(x, a = 1, b = 3, c = 7, d = 8)` will be one of | ||
#' `1`, `3`, `7`, or `8`, depending on the value of `x`. | ||
#' | ||
#' This can also be accomplished by repeated `if`/`else` statements like | ||
#' so: `if (x == "a") 1 else if (x == "b") 2 else if (x == "c") 7 else 8` | ||
#' (implicitly, the last `else` assumes x only takes 4 possible values), | ||
#' but this is more cluttered and slower (note that `switch()` takes the same | ||
#' time to evaluate regardless of the value of `x`, and is faster even | ||
#' when `x` takes the first value (here `a`), and that the `if`/`else` | ||
#' approach is roughly linear in the number of conditions that need to | ||
#' be evaluated, here up to 3 times). | ||
#' | ||
#' @examples | ||
#' # will produce lints | ||
#' lint( | ||
#' text = "if (x == 'a') 1 else if (x == 'b') 2 else 3", | ||
#' linters = if_switch_linter() | ||
#' ) | ||
#' | ||
#' # okay | ||
#' lint( | ||
#' text = "if (x == 'a') 1 else if (x == 'b' & y == 2) 2 else 3", | ||
#' linters = if_switch_linter() | ||
#' ) | ||
#' | ||
#' @evalRd rd_tags("if_switch_linter") | ||
#' @seealso [linters] for a complete list of linters available in lintr. | ||
#' @export | ||
if_switch_linter <- function() { | ||
equal_str_cond <- "expr[1][EQ and expr[STR_CONST]]" | ||
|
||
# NB: IF AND {...} AND ELSE/... implies >= 3 equality conditions are present | ||
# .//expr/IF/...: the expr in `==` that's _not_ the STR_CONST | ||
# not(preceding::IF): prevent nested matches which might be incorrect globally | ||
# not(. != .): don't match if there are _any_ expr which _don't_ match the top | ||
# expr | ||
xpath <- glue(" | ||
//IF | ||
/parent::expr[ | ||
not(preceding-sibling::IF) | ||
and {equal_str_cond} | ||
and ELSE/following-sibling::expr[ | ||
IF | ||
and {equal_str_cond} | ||
and ELSE/following-sibling::expr[IF and {equal_str_cond}] | ||
] | ||
and not( | ||
.//expr/IF/following-sibling::{equal_str_cond}/expr[not(STR_CONST)] | ||
!= expr[1][EQ]/expr[not(STR_CONST)] | ||
) | ||
] | ||
") | ||
|
||
Linter(function(source_expression) { | ||
if (!is_lint_level(source_expression, "expression")) { | ||
return(list()) | ||
} | ||
|
||
xml <- source_expression$xml_parsed_content | ||
|
||
bad_expr <- xml_find_all(xml, xpath) | ||
|
||
xml_nodes_to_lints( | ||
bad_expr, | ||
source_expression = source_expression, | ||
lint_message = paste( | ||
"Prefer switch() statements over repeated if/else equality tests,", | ||
"e.g., switch(x, a = 1, b = 2) over", | ||
'if (x == "a") 1 else if (x == "b") 2.' | ||
), | ||
type = "warning" | ||
) | ||
}) | ||
} | ||
|
||
# TODO(michaelchirico): set the lint to apply whenever there are <=3 child | ||
# expressions in any of the if/else branches. | ||
# TODO(michaelchirico): tighten the logic around this -- what exactly makes "long" | ||
# expressions more suitable for if/else vs. switch()? pick a rule apply it. |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,54 @@ | ||
test_that("if_switch_linter skips allowed usages", { | ||
linter <- if_switch_linter() | ||
|
||
# don't apply to simple if/else statements | ||
expect_lint("if (x == 'a') 1 else 2", NULL, linter) | ||
# don't apply to non-character conditions | ||
# (NB: switch _could_ be used for integral input, but this | ||
# interface is IMO a bit clunky / opaque) | ||
expect_lint("if (x == 1) 1 else 2", NULL, linter) | ||
# this also has a switch equivalent, but we don't both handling such | ||
# complicated cases | ||
expect_lint("if (x == 'a') 1 else if (x != 'b') 2 else 3", NULL, linter) | ||
# multiple variables involved --> no clean change | ||
expect_lint("if (x == 'a') 1 else if (y == 'b') 2 else 3", NULL, linter) | ||
# multiple conditions --> no clean change | ||
expect_lint("if (is.character(x) && x == 'a') 1 else if (x == 'b') 2 else 3", NULL, linter) | ||
# simple cases with two conditions might be more natural | ||
# without switch(); require at least three branches to trigger a lint | ||
expect_lint("if (x == 'a') 1 else if (x == 'b') 2", NULL, linter) | ||
# still no third if() clause | ||
expect_lint("if (x == 'a') 1 else if (x == 'b') 2 else 3", NULL, linter) | ||
}) | ||
|
||
test_that("if_switch_linter blocks simple disallowed usages", { | ||
linter <- if_switch_linter() | ||
lint_msg <- rex::rex("Prefer switch() statements over repeated if/else equality tests") | ||
|
||
# anything with >= 2 equality statements is deemed switch()-worthy | ||
expect_lint("if (x == 'a') 1 else if (x == 'b') 2 else if (x == 'c') 3", lint_msg, linter) | ||
# expressions are also OK | ||
expect_lint("if (foo(x) == 'a') 1 else if (foo(x) == 'b') 2 else if (foo(x) == 'c') 3", lint_msg, linter) | ||
}) | ||
|
||
test_that("if_switch_linter handles further nested if/else correctly", { | ||
linter <- if_switch_linter() | ||
|
||
# ensure that nested if() doesn't generate multiple lints; | ||
expect_lint( | ||
"if (x == 'a') 1 else if (x == 'b') 2 else if (x == 'c') 3 else if (x == 'd') 4", | ||
rex::rex("Prefer switch() statements over repeated if/else equality tests"), | ||
linter | ||
) | ||
# related to previous test -- if the first condition is non-`==`, the | ||
# whole if/else chain is "tainted" / non-switch()-recommended. | ||
# (technically, switch can work here, but the semantics are opaque) | ||
expect_lint( | ||
"if (x %in% c('a', 'e', 'f')) 1 else if (x == 'b') 2 else if (x == 'c') 3 else if (x == 'd') 4", | ||
NULL, | ||
linter | ||
) | ||
}) | ||
|
||
# TODO(michaelchirico): be more explicit/deliberate about nested `{}` cases like | ||
# if (x == 'a') 1 else { if (x == 'b') 2 else 3 } | ||