From 2d43a7c82f96be3bf5aaefcb83321e38845a6e14 Mon Sep 17 00:00:00 2001 From: Alexander Rosenstock Date: Mon, 2 May 2022 10:20:07 +0200 Subject: [PATCH] allow , and %>% on preceding line before { --- NEWS.md | 3 +- R/brace_linter.R | 4 +++ tests/testthat/test-brace_linter.R | 47 ++++++++++++++++++++++++++++++ 3 files changed, 53 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 34ed805b0..7dd977cc9 100644 --- a/NEWS.md +++ b/NEWS.md @@ -11,7 +11,8 @@ * 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` (#1041, @AshesITR): + `closed_curly_linter()`, also allowing `}]` in addition to `})` and `},` as exceptions. - + `open_curly_linter()`, no longer linting unnecessary trailing whitespace + + `open_curly_linter()`, no longer linting unnecessary trailing whitespace and also allowing `,` and `%>%` on + preceding lines as exceptions. (#487, #1028) + `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) diff --git a/R/brace_linter.R b/R/brace_linter.R index b0a9ce166..1580e767f 100644 --- a/R/brace_linter.R +++ b/R/brace_linter.R @@ -34,6 +34,10 @@ brace_linter <- function(allow_single_line = FALSE) { "not( (@line1 = parent::expr/preceding-sibling::OP-LEFT-BRACE/@line1) or (@line1 = following-sibling::expr/OP-LEFT-BRACE/@line1) + )", + # allow , and %>% on preceding line + "not( + @line1 = parent::expr/preceding-sibling::*[1][self::OP-COMMA or (self::SPECIAL and text() = '%>%')]/@line2 + 1 )" )) diff --git a/tests/testthat/test-brace_linter.R b/tests/testthat/test-brace_linter.R index dff057344..1a03ca128 100644 --- a/tests/testthat/test-brace_linter.R +++ b/tests/testthat/test-brace_linter.R @@ -83,6 +83,53 @@ test_that("brace_linter lints braces correctly", { linter ) + # ,<\n>{ is allowed + expect_lint( + trim_some(" + switch( + x, + 'a' = do_something(x), + 'b' = do_another(x), + { + do_first(x) + do_second(x) + } + ) + "), + NULL, + linter + ) + + expect_lint( + trim_some(" + fun( + 'This is very very very long text.', + { + message('This is the code.') + message('It\\'s stupid, but proves my point.') + } + ) + "), + NULL, + linter + ) + + # %>%\n{ is allowed + expect_lint( + trim_some(" + letters %>% + { + tibble( + lo = ., + hi = toupper(.) + ) + } %>% + mutate(row_id = row_number()) + "), + NULL, + linter + ) + # {{ }} is allowed expect_lint("{{ x }}", NULL, linter)