Skip to content

Commit

Permalink
Add param function_braces to brace_linter()
Browse files Browse the repository at this point in the history
  • Loading branch information
salim-b committed Oct 18, 2023
1 parent 4a8b931 commit f37b35b
Show file tree
Hide file tree
Showing 4 changed files with 80 additions and 20 deletions.
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@
* `object_name_linter()` no longer attempts to lint strings in function calls on the LHS of assignments (#1466, @MichaelChirico).
* `infix_spaces_linter()` allows finer control for linting `=` in different scenarios using parse tags `EQ_ASSIGN`, `EQ_SUB`, and `EQ_FORMALS` (#1977, @MichaelChirico).
* `equals_na_linter()` checks for `x %in% NA`, which is a more convoluted form of `is.na(x)` (#2088, @MichaelChirico).
* `brace_linter()`'s new `function_braces` param allows to specify whether to require function bodies to be wrapped in curly braces, with the options `"always"`, `"multi_line"` (only require curly braces when a function body spans over multiple lines), and `"never"` (#1807, #2240, @salim-b).

## New and improved features

Expand Down
41 changes: 30 additions & 11 deletions R/brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,12 @@
#' - 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.
#' - Function bodies are wrapped in curly braces.
#'
#' @param allow_single_line if `TRUE`, allow an open and closed curly pair on the same line.
#' @param allow_single_line If `TRUE`, allow an open and closed curly pair on the same line.
#' @param function_braces Character scalar specifying whether to require function bodies to be wrapped in curly braces.
#' `"multi_line"` means to only require curly braces when a function body is not on the same line as its header or it
#' spans over multiple lines.
#'
#' @examples
#' # will produce lints
Expand Down Expand Up @@ -50,7 +53,10 @@
#' - <https://style.tidyverse.org/syntax.html#indenting>
#' - <https://style.tidyverse.org/syntax.html#if-statements>
#' @export
brace_linter <- function(allow_single_line = FALSE) {
brace_linter <- function(allow_single_line = FALSE,
function_braces = c("multi_line", "always", "never")) {
function_braces <- match.arg(function_braces)

xp_cond_open <- xp_and(c(
# matching } is on same line
if (isTRUE(allow_single_line)) {
Expand Down Expand Up @@ -124,7 +130,9 @@ brace_linter <- function(allow_single_line = FALSE) {
# TODO (AshesITR): if c_style_braces is TRUE, this needs to be @line2 + 1
xp_else_same_line <- glue("//ELSE[{xp_else_closed_curly} and @line1 != {xp_else_closed_curly}/@line2]")

xp_function_brace <- "(//FUNCTION | //OP-LAMBDA)/parent::expr[@line1 != @line2 and not(expr[OP-LEFT-BRACE])]"
xp_function_brace_always <- "(//FUNCTION | //OP-LAMBDA)/parent::expr[not(expr[OP-LEFT-BRACE])]"
xp_function_brace_multi_line <-
"(//FUNCTION | //OP-LAMBDA)/parent::expr[@line1 != @line2 and not(expr[OP-LEFT-BRACE])]"

# if (x) { ... } else if (y) { ... } else { ... } is OK; fully exact pairing
# of if/else would require this to be
Expand Down Expand Up @@ -192,14 +200,25 @@ brace_linter <- function(allow_single_line = FALSE) {
)
)

lints <- c(
lints,
xml_nodes_to_lints(
xml_find_all(xml, xp_function_brace),
source_expression = source_expression,
lint_message = "Any function spanning multiple lines should use curly braces."
if (function_braces == "always") {
lints <- c(
lints,
xml_nodes_to_lints(
xml_find_all(xml, xp_function_brace_always),
source_expression = source_expression,
lint_message = "Any function body should be wrapped in curly braces."
)
)
)
} else if (function_braces == "multi_line") {
lints <- c(
lints,
xml_nodes_to_lints(
xml_find_all(xml, xp_function_brace_multi_line),
source_expression = source_expression,
lint_message = "Any function body spanning multiple lines should be wrapped in curly braces."
)
)
}

lints <- c(
lints,
Expand Down
13 changes: 10 additions & 3 deletions man/brace_linter.Rd

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

45 changes: 39 additions & 6 deletions tests/testthat/test-brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -299,24 +299,57 @@ test_that("brace_linter lints else correctly", {
})

test_that("brace_linter lints function expressions correctly", {
linter <- brace_linter()
expect_lint("function(x) 4", NULL, linter)
expect_lint(
"function(x) x + 4",
NULL,
brace_linter(function_braces = "multi_line")
)

lines <- trim_some("
function(x) {
x + 4
}
")
expect_lint(lines, NULL, linter)
expect_lint(
lines,
NULL,
brace_linter(function_braces = "multi_line")
)

msg_always <- rex::rex("Any function body should be wrapped in curly braces.")
msg_multi_line <- rex::rex("Any function body spanning multiple lines should be wrapped in curly braces.")
expect_lint(
"function(x) x + 4",
msg_always,
brace_linter(function_braces = "always")
)
lines <- trim_some("
function(x)
x+4
x + 4
")
expect_lint(
lines,
rex::rex("Any function spanning multiple lines should use curly braces."),
linter
msg_always,
brace_linter(function_braces = "always")
)
expect_lint(
lines,
msg_multi_line,
brace_linter(function_braces = "multi_line")
)
expect_lint(
lines,
NULL,
brace_linter(function_braces = "never")
)
lines <- trim_some("
function(x) x +
4
")
expect_lint(
lines,
msg_multi_line,
brace_linter(function_braces = "multi_line")
)
})

Expand Down

0 comments on commit f37b35b

Please sign in to comment.