Skip to content

Commit

Permalink
New if_else_match_braces_linter (#983)
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico authored Mar 24, 2022
1 parent 3d22c75 commit eefe67b
Show file tree
Hide file tree
Showing 13 changed files with 144 additions and 5 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ Collate:
'function_left_parentheses.R'
'get_source_expressions.R'
'ids_with_token.R'
'if_else_match_braces_linter.R'
'implicit_integer_linter.R'
'infix_spaces_linter.R'
'line_length_linter.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ export(extraction_operator_linter)
export(function_left_parentheses_linter)
export(get_source_expressions)
export(ids_with_token)
export(if_else_match_braces_linter)
export(implicit_integer_linter)
export(infix_spaces_linter)
export(line_length_linter)
Expand Down
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -97,6 +97,7 @@ function calls. (#850, #851, @renkun-ken)
* `expect_length_linter()` Require usage of `expect_length(x, n)` over `expect_equal(length(x), n)` and similar
* `expect_identical_linter()` Require usage of `expect_identical()` by default, and `expect_equal()` only by exception
* `expect_comparison_linter()` Require usage of `expect_gt(x, y)` over `expect_true(x > y)` and similar
* `if_else_match_braces_linter()` Require balanced usage of `{}` in `if`/`else` conditions
* `vector_logic_linter()` Require use of scalar logical operators (`&&` and `||`) inside `if()` conditions and similar
* `any_is_na_linter()` Require usage of `anyNA(x)` over `any(is.na(x))`
* `outer_negation_linter()` Require usage of `!any(x)` over `all(!x)` and `!all(x)` over `any(!x)`
Expand Down
46 changes: 46 additions & 0 deletions R/if_else_match_braces_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
#' Require both or neither if/else branches to use curly braces
#'
#' This linter catches `if`/`else` clauses where the `if` branch is wrapped
#' in `{...}` but the `else` branch is not, or vice versa, i.e., it ensures
#' that either both branches use `{...}` or neither does.
#'
#' @evalRd rd_tags("if_else_match_braces_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
if_else_match_braces_linter <- function() {
Linter(function(source_file) {
if (length(source_file$xml_parsed_content) == 0L) {
return(list())
}

xml <- source_file$xml_parsed_content

# if (x) { ... } else if (y) { ... } else { ... } is OK; fully exact pairing
# of if/else would require this to be
# if (x) { ... } else { if (y) { ... } else { ... } } since there's no
# elif operator/token in R, which is pretty unseemly
xpath <- "
//IF[
following-sibling::expr[2][OP-LEFT-BRACE]
and following-sibling::ELSE
/following-sibling::expr[1][not(OP-LEFT-BRACE or IF/following-sibling::expr[2][OP-LEFT-BRACE])]
]
|
//ELSE[
following-sibling::expr[1][OP-LEFT-BRACE]
and preceding-sibling::IF/following-sibling::expr[2][not(OP-LEFT-BRACE)]
]
"
bad_expr <- xml2::xml_find_all(xml, xpath)

return(lapply(
bad_expr,
xml_nodes_to_lint,
source_file = source_file,
lint_message = "Either both or neither branch in `if`/`else` should use curly braces.",
type = "warning"
))
})
}
1 change: 1 addition & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ default_linters <- with_defaults(
cyclocomp_linter(),
equals_na_linter(),
function_left_parentheses_linter(),
if_else_match_braces_linter(),
infix_spaces_linter(),
line_length_linter(),
no_tab_linter(),
Expand Down
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ expect_true_false_linter,package_development best_practices readability
expect_type_linter,package_development best_practices
extraction_operator_linter,style best_practices
function_left_parentheses_linter,style readability default
if_else_match_braces_linter,default style readability
implicit_integer_linter,style consistency best_practices
infix_spaces_linter,style readability default
line_length_linter,style readability default configurable
Expand Down
3 changes: 2 additions & 1 deletion man/default_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

19 changes: 19 additions & 0 deletions man/if_else_match_braces_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 4 additions & 3 deletions man/linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/readability_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/style_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion tests/testthat/default_linter_testcode.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ f = function (x,y = 1){}

# cyclocomp
# equals_na
# if_else_match_braces_linter
# infix_spaces
# line_length
# object_length
Expand All @@ -22,7 +23,7 @@ f = function (x,y = 1){}
someComplicatedFunctionWithALongCamelCaseName <- function(x)
{
y <- 1
if (1 > 2 && 2 > 3 && 3 > 4 && 4 > 5 && 5*10 > 6 && 5 > 6 && 6 > 7 && x == NA) {T} else {F}
if (1 > 2 && 2 > 3 && 3 > 4 && 4 > 5 && 5*10 > 6 && 5 > 6 && 6 > 7 && x == NA) {T} else F
}

# vector_logic
Expand Down
64 changes: 64 additions & 0 deletions tests/testthat/test-if_else_match_braces_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
test_that("if_else_match_braces_linter skips allowed usages", {
expect_lint("if (TRUE) 1 else 2", NULL, if_else_match_braces_linter())
expect_lint("if (TRUE) 1", NULL, if_else_match_braces_linter())

lines_brace <- trim_some("
if (TRUE) {
1
} else {
2
}
")
expect_lint(lines_brace, NULL, if_else_match_braces_linter())

# such usage is also not allowed by the style guide, but test anyway
lines_unbrace <- trim_some("
foo <- function(x) {
if (TRUE)
1
else
2
}
")
expect_lint(lines_unbrace, NULL, if_else_match_braces_linter())

# else if is OK
lines_else_if <- trim_some("
if (x) {
1
} else if (y) {
2
} else {
3
}
")
expect_lint(lines_else_if, NULL, if_else_match_braces_linter())
})

test_that("if_else_match_braces_linter blocks disallowed usage", {
lines_if <- trim_some("
foo <- function(x) {
if (x) {
1
} else 2
}
")
expect_lint(
lines_if,
rex::rex("Either both or neither branch in `if`/`else` should use curly braces."),
if_else_match_braces_linter()
)

lines_else <- trim_some("
foo <- function(x) {
if (x) 1 else {
2
}
}
")
expect_lint(
lines_else,
rex::rex("Either both or neither branch in `if`/`else` should use curly braces."),
if_else_match_braces_linter()
)
})

0 comments on commit eefe67b

Please sign in to comment.