diff --git a/DESCRIPTION b/DESCRIPTION index 6263ba5f0b..6324cd3be2 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -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' diff --git a/NAMESPACE b/NAMESPACE index 511909b67b..4f330e4c11 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -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) diff --git a/NEWS.md b/NEWS.md index 31307a789c..5a90955024 100644 --- a/NEWS.md +++ b/NEWS.md @@ -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)` diff --git a/R/if_else_match_braces_linter.R b/R/if_else_match_braces_linter.R new file mode 100644 index 0000000000..bef2863f75 --- /dev/null +++ b/R/if_else_match_braces_linter.R @@ -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" + )) + }) +} diff --git a/R/zzz.R b/R/zzz.R index fcb8232082..cf9f25655e 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -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(), diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 61c5c7dc5b..b0e6f79aed 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -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 diff --git a/man/default_linters.Rd b/man/default_linters.Rd index db52c9295c..906aa122c1 100644 --- a/man/default_linters.Rd +++ b/man/default_linters.Rd @@ -5,7 +5,7 @@ \alias{default_linters} \title{Default linters} \format{ -An object of class \code{list} of length 26. +An object of class \code{list} of length 27. } \usage{ default_linters @@ -31,6 +31,7 @@ The following linters are tagged with 'default': \item{\code{\link{cyclocomp_linter}}} \item{\code{\link{equals_na_linter}}} \item{\code{\link{function_left_parentheses_linter}}} +\item{\code{\link{if_else_match_braces_linter}}} \item{\code{\link{infix_spaces_linter}}} \item{\code{\link{line_length_linter}}} \item{\code{\link{no_tab_linter}}} diff --git a/man/if_else_match_braces_linter.Rd b/man/if_else_match_braces_linter.Rd new file mode 100644 index 0000000000..7840dfcec8 --- /dev/null +++ b/man/if_else_match_braces_linter.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/if_else_match_braces_linter.R +\name{if_else_match_braces_linter} +\alias{if_else_match_braces_linter} +\title{Require both or neither if/else branches to use curly braces} +\usage{ +if_else_match_braces_linter() +} +\description{ +This linter catches \code{if}/\verb{else} clauses where the \code{if} branch is wrapped +in \code{{...}} but the \verb{else} branch is not, or vice versa, i.e., it ensures +that either both branches use \code{{...}} or neither does. +} +\seealso{ +\link{linters} for a complete list of linters available in lintr. +} +\section{Tags}{ +\link[=default_linters]{default}, \link[=readability_linters]{readability}, \link[=style_linters]{style} +} diff --git a/man/linters.Rd b/man/linters.Rd index 10c55d7b82..0adfe901f1 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -22,12 +22,12 @@ The following tags exist: \item{\link[=configurable_linters]{configurable} (16 linters)} \item{\link[=consistency_linters]{consistency} (7 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} -\item{\link[=default_linters]{default} (26 linters)} +\item{\link[=default_linters]{default} (27 linters)} \item{\link[=efficiency_linters]{efficiency} (7 linters)} \item{\link[=package_development_linters]{package_development} (13 linters)} -\item{\link[=readability_linters]{readability} (26 linters)} +\item{\link[=readability_linters]{readability} (27 linters)} \item{\link[=robustness_linters]{robustness} (10 linters)} -\item{\link[=style_linters]{style} (31 linters)} +\item{\link[=style_linters]{style} (32 linters)} } } \section{Linters}{ @@ -56,6 +56,7 @@ The following linters exist: \item{\code{\link{expect_type_linter}} (tags: best_practices, package_development)} \item{\code{\link{extraction_operator_linter}} (tags: best_practices, style)} \item{\code{\link{function_left_parentheses_linter}} (tags: default, readability, style)} +\item{\code{\link{if_else_match_braces_linter}} (tags: default, readability, style)} \item{\code{\link{implicit_integer_linter}} (tags: best_practices, consistency, style)} \item{\code{\link{infix_spaces_linter}} (tags: default, readability, style)} \item{\code{\link{line_length_linter}} (tags: configurable, default, readability, style)} diff --git a/man/readability_linters.Rd b/man/readability_linters.Rd index de4f3c6fc1..eb8660d603 100644 --- a/man/readability_linters.Rd +++ b/man/readability_linters.Rd @@ -22,6 +22,7 @@ The following linters are tagged with 'readability': \item{\code{\link{expect_not_linter}}} \item{\code{\link{expect_true_false_linter}}} \item{\code{\link{function_left_parentheses_linter}}} +\item{\code{\link{if_else_match_braces_linter}}} \item{\code{\link{infix_spaces_linter}}} \item{\code{\link{line_length_linter}}} \item{\code{\link{object_length_linter}}} diff --git a/man/style_linters.Rd b/man/style_linters.Rd index 9f87e36a73..36d59ef702 100644 --- a/man/style_linters.Rd +++ b/man/style_linters.Rd @@ -19,6 +19,7 @@ The following linters are tagged with 'style': \item{\code{\link{cyclocomp_linter}}} \item{\code{\link{extraction_operator_linter}}} \item{\code{\link{function_left_parentheses_linter}}} +\item{\code{\link{if_else_match_braces_linter}}} \item{\code{\link{implicit_integer_linter}}} \item{\code{\link{infix_spaces_linter}}} \item{\code{\link{line_length_linter}}} diff --git a/tests/testthat/default_linter_testcode.R b/tests/testthat/default_linter_testcode.R index af6b5d4bf4..0d8cc3f4f7 100644 --- a/tests/testthat/default_linter_testcode.R +++ b/tests/testthat/default_linter_testcode.R @@ -12,6 +12,7 @@ f = function (x,y = 1){} # cyclocomp # equals_na +# if_else_match_braces_linter # infix_spaces # line_length # object_length @@ -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 diff --git a/tests/testthat/test-if_else_match_braces_linter.R b/tests/testthat/test-if_else_match_braces_linter.R new file mode 100644 index 0000000000..d52762c608 --- /dev/null +++ b/tests/testthat/test-if_else_match_braces_linter.R @@ -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() + ) +})