Skip to content

Commit 875a406

Browse files
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 <michaelchirico4@gmail.com> * add explicit test for different behaviour compared to closed_curly_linter Co-authored-by: Michael Chirico <michaelchirico4@gmail.com> Co-authored-by: Michael Chirico <michaelchirico4@gmail.com> Co-authored-by: Michael Chirico <michaelchirico4@gmail.com>
1 parent 0c985fa commit 875a406

25 files changed

+336
-268
lines changed

DESCRIPTION

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -82,11 +82,9 @@ Collate:
8282
'expect_type_linter.R'
8383
'extract.R'
8484
'extraction_operator_linter.R'
85-
'function_brace_linter.R'
8685
'function_left_parentheses.R'
8786
'get_source_expressions.R'
8887
'ids_with_token.R'
89-
'if_else_match_braces_linter.R'
9088
'ifelse_censor_linter.R'
9189
'implicit_integer_linter.R'
9290
'infix_spaces_linter.R'

NAMESPACE

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,11 +49,9 @@ export(expect_s4_class_linter)
4949
export(expect_true_false_linter)
5050
export(expect_type_linter)
5151
export(extraction_operator_linter)
52-
export(function_brace_linter)
5352
export(function_left_parentheses_linter)
5453
export(get_source_expressions)
5554
export(ids_with_token)
56-
export(if_else_match_braces_linter)
5755
export(ifelse_censor_linter)
5856
export(implicit_integer_linter)
5957
export(infix_spaces_linter)

NEWS.md

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,11 @@
1111
* 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.
1212
* Combined several curly brace related linters into a new `brace_linter` (#1041, @AshesITR):
1313
+ `closed_curly_linter()`
14+
+ `open_curly_linter()`, no longer linting unnecessary trailing whitespace
15+
+ `paren_brace_linter()`, also linting `if`/`else` and `repeat` with missing whitespace
1416
+ Require `else` to come on the same line as the preceding `}`, if present (#884, @michaelchirico)
17+
+ Require functions spanning multiple lines to use curly braces (@michaelchirico)
18+
+ Require balanced usage of `{}` in `if`/`else` conditions (@michaelchirico)
1519
* 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)
1620
+ For `lint()`, `...` is now the 3rd argument, where earlier this was `cache=`
1721
+ For `lint_dir()` and `lint_package()`, `...` is now the 2nd argument, where earlier this was `relative_path=`
@@ -117,7 +121,6 @@ function calls. (#850, #851, @renkun-ken)
117121
* `yoda_test_linter()` Require usage of `expect_identical(x, 1L)` over `expect_equal(1L, x)` and similar
118122
* `expect_identical_linter()` Require usage of `expect_identical()` by default, and `expect_equal()` only by exception
119123
* `expect_comparison_linter()` Require usage of `expect_gt(x, y)` over `expect_true(x > y)` and similar
120-
* `if_else_match_braces_linter()` Require balanced usage of `{}` in `if`/`else` conditions
121124
* `vector_logic_linter()` Require use of scalar logical operators (`&&` and `||`) inside `if()` conditions and similar
122125
* `any_is_na_linter()` Require usage of `anyNA(x)` over `any(is.na(x))`
123126
* `class_equals_linter()` Prevent comparing `class(x)` with `==`, `!=`, or `%in%`, where `inherits()` is typically preferred
@@ -131,7 +134,10 @@ function calls. (#850, #851, @renkun-ken)
131134
* `nested_ifelse_linter()` Prevent nested calls to `ifelse()` like `ifelse(A, x, ifelse(B, y, z))`, and similar
132135
* `condition_message_linter` Prevent condition messages from being constructed like `stop(paste(...))` (where just `stop(...)` is preferable)
133136
* `redundant_ifelse_linter()` Prevent usage like `ifelse(A & B, TRUE, FALSE)` or `ifelse(C, 0, 1)` (the latter is `as.numeric(!C)`)
134-
* `brace_linter()` Require `else` to come on the same line as the preceding `}`, if present
137+
* Extensions to `brace_linter()`
138+
+ Require `else` to come on the same line as the preceding `}`, if present
139+
+ Require balanced usage of `{}` in `if`/`else` conditions
140+
+ Require functions spanning multiple lines to use curly braces
135141
* `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!)
136142
* `regex_subset_linter()` Require usage of `grep(ptn, x, value = TRUE)` over `x[grep(ptn, x)]` and similar
137143
* `consecutive_stopifnot_linter()` Require consecutive calls to `stopifnot()` to be unified into one

R/brace_linter.R

Lines changed: 89 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,20 @@
22
#'
33
#' Perform various style checks related to placement and spacing of curly braces:
44
#'
5-
#' - Curly braces are on their own line unless they are followed by an `else`.
5+
#' - Opening curly braces are never on their own line and are always followed by a newline.
6+
#' - Opening curly braces have a space before them.
7+
#' - Closing curly braces are on their own line unless they are followed by an `else`.
68
#' - Closing curly braces in `if` conditions are on the same line as the corresponding `else`.
9+
#' - Either both or neither branch in `if`/`else` use curly braces, i.e., either both branches use `{...}` or neither
10+
#' does.
11+
#' - Functions spanning multiple lines use curly braces.
712
#'
813
#' @param allow_single_line if `TRUE`, allow an open and closed curly pair on the same line.
914
#'
1015
#' @evalRd rd_tags("brace_linter")
11-
#' @seealso [linters] for a complete list of linters available in lintr.
16+
#' @seealso [linters] for a complete list of linters available in lintr. \cr
17+
#' <https://style.tidyverse.org/syntax.html#indenting> \cr
18+
#' <https://style.tidyverse.org/syntax.html#if-statements>
1219
#' @export
1320
brace_linter <- function(allow_single_line = FALSE) {
1421
Linter(function(source_expression) {
@@ -18,6 +25,51 @@ brace_linter <- function(allow_single_line = FALSE) {
1825

1926
lints <- list()
2027

28+
xp_cond_open <- xp_and(c(
29+
# matching } is on same line
30+
if (isTRUE(allow_single_line)) {
31+
"(@line1 != following-sibling::OP-LEFT-BRACE/@line1)"
32+
},
33+
# double curly
34+
"not(
35+
(@line1 = parent::expr/preceding-sibling::OP-LEFT-BRACE/@line1) or
36+
(@line1 = following-sibling::expr/OP-LEFT-BRACE/@line1)
37+
)"
38+
))
39+
40+
# TODO (AshesITR): if c_style_braces is TRUE, invert the preceding-sibling condition
41+
xp_open_curly <- glue::glue("//OP-LEFT-BRACE[
42+
{ xp_cond_open } and (
43+
not(@line1 = parent::expr/preceding-sibling::*/@line2) or
44+
@line1 = following-sibling::*[1][not(self::COMMENT)]/@line1
45+
)
46+
]")
47+
48+
lints <- c(lints, lapply(
49+
xml2::xml_find_all(source_expression$xml_parsed_content, xp_open_curly),
50+
xml_nodes_to_lint,
51+
source_file = source_expression,
52+
lint_message = paste(
53+
"Opening curly braces should never go on their own line and",
54+
"should always be followed by a new line."
55+
)
56+
))
57+
58+
xp_open_preceding <- "parent::expr/preceding-sibling::*[1][self::OP-RIGHT-PAREN or self::ELSE or self::REPEAT]"
59+
60+
xp_paren_brace <- glue::glue("//OP-LEFT-BRACE[
61+
@line1 = { xp_open_preceding }/@line1
62+
and
63+
@col1 = { xp_open_preceding }/@col2 + 1
64+
]")
65+
66+
lints <- c(lints, lapply(
67+
xml2::xml_find_all(source_expression$xml_parsed_content, xp_paren_brace),
68+
xml_nodes_to_lint,
69+
source_file = source_expression,
70+
lint_message = "There should be a space before an opening curly brace."
71+
))
72+
2173
xp_cond_closed <- xp_and(c(
2274
# matching { is on same line
2375
if (isTRUE(allow_single_line)) {
@@ -63,6 +115,41 @@ brace_linter <- function(allow_single_line = FALSE) {
63115
lint_message = "`else` should come on the same line as the previous `}`."
64116
))
65117

118+
xp_function_brace <- "//expr[FUNCTION and @line1 != @line2 and not(expr[OP-LEFT-BRACE])]"
119+
120+
lints <- c(lints, lapply(
121+
xml2::xml_find_all(source_expression$xml_parsed_content, xp_function_brace),
122+
xml_nodes_to_lint,
123+
source_file = source_expression,
124+
lint_message = "Any function spanning multiple lines should use curly braces."
125+
))
126+
127+
# if (x) { ... } else if (y) { ... } else { ... } is OK; fully exact pairing
128+
# of if/else would require this to be
129+
# if (x) { ... } else { if (y) { ... } else { ... } } since there's no
130+
# elif operator/token in R, which is pretty unseemly
131+
xp_if_else_match_brace <- "
132+
//IF[
133+
following-sibling::expr[2][OP-LEFT-BRACE]
134+
and following-sibling::ELSE
135+
/following-sibling::expr[1][not(OP-LEFT-BRACE or IF/following-sibling::expr[2][OP-LEFT-BRACE])]
136+
]
137+
138+
|
139+
140+
//ELSE[
141+
following-sibling::expr[1][OP-LEFT-BRACE]
142+
and preceding-sibling::IF/following-sibling::expr[2][not(OP-LEFT-BRACE)]
143+
]
144+
"
145+
146+
lints <- c(lints, lapply(
147+
xml2::xml_find_all(source_expression$xml_parsed_content, xp_if_else_match_brace),
148+
xml_nodes_to_lint,
149+
source_file = source_expression,
150+
lint_message = "Either both or neither branch in `if`/`else` should use curly braces."
151+
))
152+
66153
lints
67154
})
68155
}

R/function_brace_linter.R

Lines changed: 0 additions & 30 deletions
This file was deleted.

R/if_else_match_braces_linter.R

Lines changed: 0 additions & 48 deletions
This file was deleted.

R/open_curly_linter.R

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
#' <https://style.tidyverse.org/syntax.html#indenting>
1010
#' @export
1111
open_curly_linter <- function(allow_single_line = FALSE) {
12+
lintr_deprecated("open_curly_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
1213
Linter(function(source_file) {
1314
lapply(
1415
ids_with_token(source_file, "'{'"),

R/paren_brace_linter.R

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
#' @seealso [linters] for a complete list of linters available in lintr.
77
#' @export
88
paren_brace_linter <- function() {
9+
lintr_deprecated("paren_brace_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
910
Linter(function(source_file) {
1011
if (is.null(source_file$xml_parsed_content)) {
1112
return(NULL)

R/zzz.R

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,18 +18,14 @@ default_linters <- with_defaults(
1818
commented_code_linter(),
1919
cyclocomp_linter(),
2020
equals_na_linter(),
21-
function_brace_linter(),
2221
function_left_parentheses_linter(),
23-
if_else_match_braces_linter(),
2422
infix_spaces_linter(),
2523
line_length_linter(),
2624
no_tab_linter(),
2725
object_length_linter(),
2826
object_name_linter(),
2927
object_usage_linter(),
30-
open_curly_linter(),
3128
paren_body_linter(),
32-
paren_brace_linter(),
3329
pipe_continuation_linter(),
3430
semicolon_linter(),
3531
seq_linter(),

inst/lintr/linters.csv

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -26,9 +26,7 @@ expect_s4_class_linter,package_development best_practices
2626
expect_true_false_linter,package_development best_practices readability
2727
expect_type_linter,package_development best_practices
2828
extraction_operator_linter,style best_practices
29-
function_brace_linter,default style readability
3029
function_left_parentheses_linter,style readability default
31-
if_else_match_braces_linter,default style readability
3230
ifelse_censor_linter,best_practices efficiency
3331
implicit_integer_linter,style consistency best_practices
3432
infix_spaces_linter,style readability default
@@ -45,11 +43,11 @@ numeric_leading_zero_linter,style consistency readability
4543
object_length_linter,style readability default configurable
4644
object_name_linter,style consistency default configurable
4745
object_usage_linter,style readability correctness default
48-
open_curly_linter,style readability default configurable
46+
open_curly_linter,style readability configurable
4947
outer_negation_linter,readability efficiency best_practices
5048
package_hooks_linter,style correctness package_development
5149
paren_body_linter,style readability default
52-
paren_brace_linter,style readability default
50+
paren_brace_linter,style readability
5351
paste_linter,best_practices consistency
5452
pipe_call_linter,style readability
5553
pipe_continuation_linter,style readability default

man/brace_linter.Rd

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

man/default_linters.Rd

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

man/function_brace_linter.Rd

Lines changed: 0 additions & 19 deletions
This file was deleted.

0 commit comments

Comments
 (0)