Skip to content

Commit

Permalink
Unified brace_linter (#1092)
Browse files Browse the repository at this point in the history
* create brace_linter based on XPath

 - deprecate closed_curly_linter
 - add brace_linter to defaults instead of closed_curly_linter
 - add breaking change to NEWS

* fix missing newline, update warning tests for semicolon_terminator_linter

* test for closed_curly_linter warning and make tests more silent

* remove c_style_braces for now

* document()

* allow ]}, update NEWS, incorporate feedback, fix lint

* delete else_same_line_linter and merge it into brace_linter (#1093)

* delete else_same_line_linter and merge it into brace_linter

* delete function_brace_linter and merge it into brace_linter (#1094)

* delete function_brace_linter and merge it into brace_linter

* delete if_else_match_braces_linter and merge it into brace_linter (#1095)

* delete if_else_match_braces_linter and merge it into brace_linter

* deprecate open_curly_linter and merge it into brace_linter (#1096)

* deprecate open_curly_linter

 - remove open_curly_linter from defaults
 - refactor to XPath based approach
 - no longer lint trailing whitespace (there's a separate linter for that)

* merge paren_brace_linter into brace_linter (#1097)

* deprecate paren_brace_linter

 - remove paren_brace_linter from defaults
 - extend to else{ and repeat{

* `code`

Co-authored-by: Michael Chirico <[email protected]>

* add explicit test for different behaviour compared to closed_curly_linter

Co-authored-by: Michael Chirico <[email protected]>

Co-authored-by: Michael Chirico <[email protected]>

Co-authored-by: Michael Chirico <[email protected]>

Co-authored-by: Michael Chirico <[email protected]>

Co-authored-by: Michael Chirico <[email protected]>
  • Loading branch information
AshesITR and MichaelChirico authored Apr 26, 2022
1 parent 56fec1b commit b4d39bb
Show file tree
Hide file tree
Showing 34 changed files with 610 additions and 394 deletions.
4 changes: 1 addition & 3 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ Collate:
'any_is_na_linter.R'
'assignment_linter.R'
'backport_linter.R'
'brace_linter.R'
'cache.R'
'class_equals_linter.R'
'closed_curly_linter.R'
Expand All @@ -67,7 +68,6 @@ Collate:
'declared_functions.R'
'deprecated.R'
'duplicate_argument_linter.R'
'else_same_line_linter.R'
'equals_na_linter.R'
'exclude.R'
'expect_comparison_linter.R'
Expand All @@ -82,11 +82,9 @@ Collate:
'expect_type_linter.R'
'extract.R'
'extraction_operator_linter.R'
'function_brace_linter.R'
'function_left_parentheses.R'
'get_source_expressions.R'
'ids_with_token.R'
'if_else_match_braces_linter.R'
'ifelse_censor_linter.R'
'implicit_integer_linter.R'
'infix_spaces_linter.R'
Expand Down
4 changes: 1 addition & 3 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ export(assignment_linter)
export(available_linters)
export(available_tags)
export(backport_linter)
export(brace_linter)
export(checkstyle_output)
export(class_equals_linter)
export(clear_cache)
Expand All @@ -34,7 +35,6 @@ export(default_settings)
export(default_undesirable_functions)
export(default_undesirable_operators)
export(duplicate_argument_linter)
export(else_same_line_linter)
export(equals_na_linter)
export(expect_comparison_linter)
export(expect_identical_linter)
Expand All @@ -49,11 +49,9 @@ export(expect_s4_class_linter)
export(expect_true_false_linter)
export(expect_type_linter)
export(extraction_operator_linter)
export(function_brace_linter)
export(function_left_parentheses_linter)
export(get_source_expressions)
export(ids_with_token)
export(if_else_match_braces_linter)
export(ifelse_censor_linter)
export(implicit_integer_linter)
export(infix_spaces_linter)
Expand Down
15 changes: 13 additions & 2 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,15 @@
* Consistent access to linters through a function call, even for linters without parameters (#245, @fangly, @AshesITR, and @MichaelChirico)
* Removed deprecated functions `absolute_paths_linter`, `camel_case_linter`, `multiple_dots_linter`, `snake_case_linter`, and `trailing_semicolons_linter`. They have been marked as deprecated since v1.0.1, which was released in 2017.
* Rename `semicolon_terminator_linter` to `semicolon_linter` for better consistency. `semicolon_terminator_linter` survives but is marked for deprecation. The new linter also has a new signature, taking arguments `allow_compound` and `allow_trailing` to replace the old single argument `semicolon=`, again for signature consistency with other linters.
* Combined several curly brace related linters into a new `brace_linter`:
+ `closed_curly_linter()`, also allowing `}]` in addition to `})` and `},` as exceptions.
* Combined several curly brace related linters into a new `brace_linter` (#1041, @AshesITR):
+ `closed_curly_linter()`
+ `open_curly_linter()`, no longer linting unnecessary trailing whitespace
+ `paren_brace_linter()`, also linting `if`/`else` and `repeat` with missing whitespace
+ Require `else` to come on the same line as the preceding `}`, if present (#884, @michaelchirico)
+ Require functions spanning multiple lines to use curly braces (@michaelchirico)
+ Require balanced usage of `{}` in `if`/`else` conditions (@michaelchirico)
* The `...` arguments for `lint()`, `lint_dir()`, and `lint_package()` have promoted to an earlier position to better match the [Tidyverse design principal](https://design.tidyverse.org/args-data-details.html) of data->descriptor->details. This change enables passing objects to `...` without needing to specify non-required arguments, e.g. `lint_dir("/path/to/dir", linter())` now works without the need to specify `relative_path`. This affects some code that uses positional arguments. (#935, @michaelchirico)
+ For `lint()`, `...` is now the 3rd argument, where earlier this was `cache=`
+ For `lint_dir()` and `lint_package()`, `...` is now the 2nd argument, where earlier this was `relative_path=`
Expand Down Expand Up @@ -117,7 +126,6 @@ function calls. (#850, #851, @renkun-ken)
+ Extended for #1067 to exclude `$` extractions like `expect_equal(x$"key", 2)`
* `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))`
* `class_equals_linter()` Prevent comparing `class(x)` with `==`, `!=`, or `%in%`, where `inherits()` is typically preferred
Expand All @@ -131,7 +139,10 @@ function calls. (#850, #851, @renkun-ken)
* `nested_ifelse_linter()` Prevent nested calls to `ifelse()` like `ifelse(A, x, ifelse(B, y, z))`, and similar
* `condition_message_linter` Prevent condition messages from being constructed like `stop(paste(...))` (where just `stop(...)` is preferable)
* `redundant_ifelse_linter()` Prevent usage like `ifelse(A & B, TRUE, FALSE)` or `ifelse(C, 0, 1)` (the latter is `as.numeric(!C)`)
* `else_same_line_linter()` Require `else` to come on the same line as the preceding `}`, if present
* Extensions to `brace_linter()`
+ Require `else` to come on the same line as the preceding `}`, if present
+ Require balanced usage of `{}` in `if`/`else` conditions
+ Require functions spanning multiple lines to use curly braces
* `unreachable_code_linter()` Prevent code after `return()` and `stop()` statements that will never be reached (extended for #1051 thanks to early user testing, thanks @bersbersbers!)
* `regex_subset_linter()` Require usage of `grep(ptn, x, value = TRUE)` over `x[grep(ptn, x)]` and similar
* `consecutive_stopifnot_linter()` Require consecutive calls to `stopifnot()` to be unified into one
Expand Down
159 changes: 159 additions & 0 deletions R/brace_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,159 @@
#' Brace linter
#'
#' Perform various style checks related to placement and spacing of curly braces:
#'
#' - Opening curly braces are never on their own line and are always followed by a newline.
#' - Opening curly braces have a space before them.
#' - Closing curly braces are on their own line unless they are followed by an `else`.
#' - Closing curly braces in `if` conditions are on the same line as the corresponding `else`.
#' - Either both or neither branch in `if`/`else` use curly braces, i.e., either both branches use `{...}` or neither
#' does.
#' - Functions spanning multiple lines use curly braces.
#'
#' @param allow_single_line if `TRUE`, allow an open and closed curly pair on the same line.
#'
#' @evalRd rd_tags("brace_linter")
#' @seealso [linters] for a complete list of linters available in lintr. \cr
#' <https://style.tidyverse.org/syntax.html#indenting> \cr
#' <https://style.tidyverse.org/syntax.html#if-statements>
#' @export
brace_linter <- function(allow_single_line = FALSE) {
Linter(function(source_expression) {
if (length(source_expression$xml_parsed_content) == 0L) {
return(list())
}

lints <- list()

xp_cond_open <- xp_and(c(
# matching } is on same line
if (isTRUE(allow_single_line)) {
"(@line1 != following-sibling::OP-LEFT-BRACE/@line1)"
},
# double curly
"not(
(@line1 = parent::expr/preceding-sibling::OP-LEFT-BRACE/@line1) or
(@line1 = following-sibling::expr/OP-LEFT-BRACE/@line1)
)"
))

# TODO (AshesITR): if c_style_braces is TRUE, invert the preceding-sibling condition
xp_open_curly <- glue::glue("//OP-LEFT-BRACE[
{ xp_cond_open } and (
not(@line1 = parent::expr/preceding-sibling::*/@line2) or
@line1 = following-sibling::*[1][not(self::COMMENT)]/@line1
)
]")

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_open_curly),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = paste(
"Opening curly braces should never go on their own line and",
"should always be followed by a new line."
)
))

xp_open_preceding <- "parent::expr/preceding-sibling::*[1][self::OP-RIGHT-PAREN or self::ELSE or self::REPEAT]"

xp_paren_brace <- glue::glue("//OP-LEFT-BRACE[
@line1 = { xp_open_preceding }/@line1
and
@col1 = { xp_open_preceding }/@col2 + 1
]")

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_paren_brace),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = "There should be a space before an opening curly brace."
))

xp_cond_closed <- xp_and(c(
# matching { is on same line
if (isTRUE(allow_single_line)) {
"(@line1 != preceding-sibling::OP-LEFT-BRACE/@line1)"
},
# immediately followed by ",", "]" or ")"
"not(
@line1 = ancestor::expr/following-sibling::*[1][
self::OP-COMMA or self::OP-RIGHT-BRACKET or self::OP-RIGHT-PAREN
]/@line1
)",
# double curly
"not(
(@line1 = parent::expr/following-sibling::OP-RIGHT-BRACE/@line1) or
(@line1 = preceding-sibling::expr/OP-RIGHT-BRACE/@line1)
)"
))

# TODO (AshesITR): if c_style_braces is TRUE, skip the not(ELSE) condition
xp_closed_curly <- glue::glue("//OP-RIGHT-BRACE[
{ xp_cond_closed } and (
(@line1 = preceding-sibling::*[1]/@line2) or
(@line1 = parent::expr/following-sibling::*[1][not(self::ELSE)]/@line1)
)
]")

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_closed_curly),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = paste(
"Closing curly-braces should always be on their own line,",
"unless they are followed by an else."
)
))

xp_else_closed_curly <- "preceding-sibling::IF/following-sibling::expr[2]/OP-RIGHT-BRACE"
# need to (?) repeat previous_curly_path since != will return true if there is
# no such node. ditto for approach with not(@line1 = ...).
# TODO (AshesITR): if c_style_braces is TRUE, this needs to be @line2 + 1
xp_else_same_line <- glue::glue("//ELSE[{xp_else_closed_curly} and @line1 != {xp_else_closed_curly}/@line2]")

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_else_same_line),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = "`else` should come on the same line as the previous `}`."
))

xp_function_brace <- "//expr[FUNCTION and @line1 != @line2 and not(expr[OP-LEFT-BRACE])]"

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_function_brace),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = "Any function spanning multiple lines should use curly braces."
))

# 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
xp_if_else_match_brace <- "
//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)]
]
"

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_if_else_match_brace),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = "Either both or neither branch in `if`/`else` should use curly braces."
))

lints
})
}
4 changes: 3 additions & 1 deletion R/closed_curly_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
#' <https://style.tidyverse.org/syntax.html#indenting>
#' @export
closed_curly_linter <- function(allow_single_line = FALSE) {
lintr_deprecated("closed_curly_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
Linter(function(source_file) {
lapply(ids_with_token(source_file, "'}'"),
function(id) {
Expand Down Expand Up @@ -66,7 +67,8 @@ closed_curly_linter <- function(allow_single_line = FALSE) {
"unless they are followed by an else."
),
line = source_file$lines[as.character(parsed$line1)]
)}
)
}
}
)
})
Expand Down
31 changes: 0 additions & 31 deletions R/else_same_line_linter.R

This file was deleted.

30 changes: 0 additions & 30 deletions R/function_brace_linter.R

This file was deleted.

48 changes: 0 additions & 48 deletions R/if_else_match_braces_linter.R

This file was deleted.

1 change: 1 addition & 0 deletions R/open_curly_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
#' <https://style.tidyverse.org/syntax.html#indenting>
#' @export
open_curly_linter <- function(allow_single_line = FALSE) {
lintr_deprecated("open_curly_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
Linter(function(source_file) {
lapply(
ids_with_token(source_file, "'{'"),
Expand Down
1 change: 1 addition & 0 deletions R/paren_brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
paren_brace_linter <- function() {
lintr_deprecated("paren_brace_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
Linter(function(source_file) {
if (is.null(source_file$xml_parsed_content)) {
return(NULL)
Expand Down
Loading

0 comments on commit b4d39bb

Please sign in to comment.