diff --git a/NEWS.md b/NEWS.md index 5e7302557..ae7799c09 100644 --- a/NEWS.md +++ b/NEWS.md @@ -10,6 +10,10 @@ + Linters `closed_curly_linter()`, `open_curly_linter()`, `paren_brace_linter()`, and `semicolon_terminator_linter()`. + `linter=` argument of `Lint()`. +## New and improved features + +* `brace_linter()`' has a new argument `function_bodies` (default `"multi_line"`) which controls when 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 multiple lines), `"not_inline"` (only require curly braces when a function body starts on a new line) and `"never"` (#1807, #2240, @salim-b). + ## Notes * `expect_lint_free()` and other functions that rely on the {testthat} framework now have a consistent error message. (#2585, @F-Noelle). diff --git a/R/brace_linter.R b/R/brace_linter.R index 7eda5a714..4c7add043 100644 --- a/R/brace_linter.R +++ b/R/brace_linter.R @@ -8,9 +8,14 @@ #' - 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_bodies When to require function bodies to be wrapped in curly braces. One of +#' - `"always"` to require braces around all function bodies, including inline functions, +#' - `"not_inline"` to require braces when a function body does not start on the same line as its signature, +#' - `"multi_line"` (the default) to require braces when a function definition spans multiple lines, +#' - `"never"` to never require braces in function bodies. #' #' @examples #' # will produce lints @@ -50,7 +55,10 @@ #' - #' - #' @export -brace_linter <- function(allow_single_line = FALSE) { +brace_linter <- function(allow_single_line = FALSE, + function_bodies = c("multi_line", "always", "not_inline", "never")) { + function_bodies <- match.arg(function_bodies) + xp_cond_open <- xp_and(c( # matching } is on same line if (isTRUE(allow_single_line)) { @@ -124,7 +132,25 @@ brace_linter <- function(allow_single_line = FALSE) { # TODO(#1103): 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])]" + if (function_bodies != "never") { + xp_cond_function_brace <- switch( + function_bodies, + always = "1", + multi_line = "@line1 != @line2", + not_inline = "@line1 != expr/@line1" + ) + + xp_function_brace <- glue( + "(//FUNCTION | //OP-LAMBDA)/parent::expr[{xp_cond_function_brace} and not(expr/OP-LEFT-BRACE)]" + ) + + msg_function_brace <- switch( + function_bodies, + always = "Wrap function bodies in curly braces.", + multi_line = "Wrap multi-line function bodies in curly braces.", + not_inline = "Wrap function bodies starting on a new line in curly braces." + ) + } # if (x) { ... } else if (y) { ... } else { ... } is OK; fully exact pairing # of if/else would require this to be @@ -188,15 +214,16 @@ brace_linter <- function(allow_single_line = FALSE) { lint_message = "`else` should come on the same line as the previous `}`." ) ) - - lints <- c( - lints, - xml_nodes_to_lints( - xml_find_all(xml, xp_function_brace), - source_expression = source_expression, - lint_message = "Use curly braces for any function spanning multiple lines." + if (function_bodies != "never") { + lints <- c( + lints, + xml_nodes_to_lints( + xml_find_all(xml, xp_function_brace), + source_expression = source_expression, + lint_message = msg_function_brace + ) ) - ) + } lints <- c( lints, diff --git a/man/brace_linter.Rd b/man/brace_linter.Rd index 3fb01e06c..1270c6743 100644 --- a/man/brace_linter.Rd +++ b/man/brace_linter.Rd @@ -4,10 +4,21 @@ \alias{brace_linter} \title{Brace linter} \usage{ -brace_linter(allow_single_line = FALSE) +brace_linter( + allow_single_line = FALSE, + function_bodies = c("multi_line", "always", "not_inline", "never") +) } \arguments{ -\item{allow_single_line}{if \code{TRUE}, allow an open and closed curly pair on the same line.} +\item{allow_single_line}{If \code{TRUE}, allow an open and closed curly pair on the same line.} + +\item{function_bodies}{When to require function bodies to be wrapped in curly braces. One of +\itemize{ +\item \code{"always"} to require braces around all function bodies, including inline functions, +\item \code{"not_inline"} to require braces when a function body does not start on the same line as its signature, +\item \code{"multi_line"} (the default) to require braces when a function definition spans multiple lines, +\item \code{"never"} to never require braces in function bodies. +}} } \description{ Perform various style checks related to placement and spacing of curly braces: @@ -20,7 +31,7 @@ Perform various style checks related to placement and spacing of curly braces: \item Closing curly braces in \code{if} conditions are on the same line as the corresponding \verb{else}. \item Either both or neither branch in \code{if}/\verb{else} use curly braces, i.e., either both branches use \code{{...}} or neither does. -\item Functions spanning multiple lines use curly braces. +\item Function bodies are wrapped in curly braces. } } \examples{ diff --git a/tests/testthat/test-brace_linter.R b/tests/testthat/test-brace_linter.R index 3727e4c96..5bc8eb3dd 100644 --- a/tests/testthat/test-brace_linter.R +++ b/tests/testthat/test-brace_linter.R @@ -299,25 +299,82 @@ 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) + msg_always <- rex::rex("Wrap function bodies in curly braces.") + msg_multi_line <- rex::rex("Wrap multi-line function bodies in curly braces.") + msg_not_inline <- rex::rex("Wrap function bodies starting on a new line in curly braces.") + msgs_open_close <- list( + rex::rex("Opening curly braces should never go on their own line and should always be followed by a new line."), + rex::rex("Closing curly-braces should always be on their own line, unless they are followed by an else.") + ) + + linter_always <- brace_linter(function_bodies = "always") + linter_multi_line <- brace_linter(function_bodies = "multi_line") + linter_not_inline <- brace_linter(function_bodies = "not_inline") + linter_never <- brace_linter(function_bodies = "never") lines <- trim_some(" function(x) { x + 4 } ") - expect_lint(lines, NULL, linter) + expect_no_lint(lines, linter_always) + expect_no_lint(lines, linter_multi_line) + expect_no_lint(lines, linter_not_inline) + expect_no_lint(lines, linter_never) + + expect_lint("function(x) { x + 4 }", msgs_open_close, linter_always) + expect_lint("function(x) { x + 4 }", msgs_open_close, linter_multi_line) + expect_lint("function(x) { x + 4 }", msgs_open_close, linter_not_inline) + expect_lint("function(x) { x + 4 }", msgs_open_close, linter_never) + # function_bodies = "always" should only prohibit inline functions with allow_single_line = FALSE (the default): + expect_no_lint( + "function(x) { x + 4 }", + brace_linter(allow_single_line = TRUE, function_bodies = "always") + ) + + expect_lint("function(x) x + 4", msg_always, linter_always) + expect_no_lint("function(x) x + 4", linter_multi_line) + expect_no_lint("function(x) x + 4", linter_not_inline) + expect_no_lint("function(x) x + 4", linter_never) + + lines <- trim_some(" + function(x) x + + 4 + ") + expect_lint(lines, msg_always, linter_always) + expect_lint(lines, msg_multi_line, linter_multi_line) + expect_no_lint(lines, linter_not_inline) + expect_no_lint(lines, linter_never) lines <- trim_some(" function(x) - x+4 + x + 4 ") - expect_lint( - lines, - rex::rex("Use curly braces for any function spanning multiple lines."), - linter - ) + expect_lint(lines, msg_always, linter_always) + expect_lint(lines, msg_multi_line, linter_multi_line) + expect_lint(lines, msg_not_inline, linter_not_inline) + expect_no_lint(lines, linter_never) + + # missing newline after opening brace; closing brace not on sep line + lines <- trim_some(" + foo <- function(x) { x + + 4 } + ") + expect_lint(lines, msgs_open_close, linter_always) + expect_lint(lines, msgs_open_close, linter_multi_line) + expect_lint(lines, msgs_open_close, linter_not_inline) + expect_lint(lines, msgs_open_close, linter_never) + + # fn body wrapped in additional unneeded parentheses + lines <- trim_some(" + foo <- function(x) ({ + x + 1 + }) + ") + expect_lint(lines, msg_always, linter_always) + expect_lint(lines, msg_multi_line, linter_multi_line) + expect_no_lint(lines, linter_not_inline) + expect_no_lint(lines, linter_never) }) test_that("brace_linter lints if/else matching braces correctly", {