-
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.
* 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
1 parent
56fec1b
commit b4d39bb
Showing
34 changed files
with
610 additions
and
394 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,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 | ||
}) | ||
} |
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 was deleted.
Oops, something went wrong.
This file was deleted.
Oops, something went wrong.
This file was deleted.
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
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
Oops, something went wrong.