From 2530f99e48831326c77630f5812ac9ae5b5a1ccf Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Thu, 28 Nov 2024 20:20:08 +0100 Subject: [PATCH 01/15] Add rule to reduce blank lines between scopes --- R/rules-line-breaks.R | 18 ++++++++++++++++++ R/style-guides.R | 1 + tests/testthat/alignment/named-out.R | 1 - .../indention_curly_brackets/custom-out.R | 1 - .../line_breaks_and_other/assignment-out.R | 2 -- .../line_breaks_fun_call/blank-strict-out.R | 1 - .../switch_ifelse_etc_no_line_break-out.R | 1 - .../token_dependent_mixed-out.R | 1 - .../parse_comments/with_indention-out.R | 2 -- .../13-empty-lines-out.R | 2 -- .../26-empty-trailing-lines-out.R | 1 - tests/testthat/test-transformers-drop.R | 1 + .../token_adding_removing/mixed_token-out.R | 1 - 13 files changed, 20 insertions(+), 13 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 07229ebc9..1e834ab77 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -447,3 +447,21 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { pd } + + +#' Reduce multiple blank lines to a maximum number of allowed blank lines +#' @param pd_flat A flat parse table. +#' @param allowed_blank_lines The maximum number of allowed blank lines between code elements. Default is `2L`. +#' @keywords internal +reduce_extra_blank_lines_between_scopes <- function(pd_flat, allowed_blank_lines = 2L) { + # Calculate the maximum allowed lag_newlines + max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token + + # Identify positions where lag_newlines exceed the maximum allowed + idx <- which(pd_flat$lag_newlines > max_lag_newlines) + + # Reduce lag_newlines to the maximum allowed at those positions + pd_flat$lag_newlines[idx] <- max_lag_newlines + + return(pd_flat) +} diff --git a/R/style-guides.R b/R/style-guides.R index 39fc30118..c61392d1f 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -139,6 +139,7 @@ tidyverse_style <- function(scope = "tokens", if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = if (strict) remove_line_breaks_in_fun_dec, + reduce_extra_blank_lines_between_scopes = reduce_extra_blank_lines_between_scopes, style_line_break_around_curly = partial( style_line_break_around_curly, strict diff --git a/tests/testthat/alignment/named-out.R b/tests/testthat/alignment/named-out.R index 5fd8e9507..35c3bb607 100644 --- a/tests/testthat/alignment/named-out.R +++ b/tests/testthat/alignment/named-out.R @@ -102,7 +102,6 @@ call( ) - # if all col1 arguments are named, col1 must also be aligned # not aligned fell( diff --git a/tests/testthat/indention_curly_brackets/custom-out.R b/tests/testthat/indention_curly_brackets/custom-out.R index f2612d575..f68775003 100644 --- a/tests/testthat/indention_curly_brackets/custom-out.R +++ b/tests/testthat/indention_curly_brackets/custom-out.R @@ -4,7 +4,6 @@ if (value > 0) { } - if (value > 0) { print(value) } diff --git a/tests/testthat/line_breaks_and_other/assignment-out.R b/tests/testthat/line_breaks_and_other/assignment-out.R index 239bb02aa..5c16559ed 100644 --- a/tests/testthat/line_breaks_and_other/assignment-out.R +++ b/tests/testthat/line_breaks_and_other/assignment-out.R @@ -22,7 +22,6 @@ x <- 3 - ImportantDataFrame$ImportantColumn1 <- ImportantDataFrame$ImportantColumn2 <- ComplicatedFunction(ImportantDataFrame$InputColumn) @@ -32,6 +31,5 @@ ImportantDataFrame$ImportantColumn1 <- ImportantDataFrame$ImportantColumn2 <- ComplicatedFunction(ImportantDataFrame$InputColumn) - ImportantDataFrame$ImportantColumn1 <- ImportantDataFrame$ImportantColumn2 <- ComplicatedFunction(ImportantDataFrame$InputColumn) diff --git a/tests/testthat/line_breaks_fun_call/blank-strict-out.R b/tests/testthat/line_breaks_fun_call/blank-strict-out.R index cb9acea09..19232c9fa 100644 --- a/tests/testthat/line_breaks_fun_call/blank-strict-out.R +++ b/tests/testthat/line_breaks_fun_call/blank-strict-out.R @@ -19,7 +19,6 @@ call( 2, - # comment 1, diff --git a/tests/testthat/line_breaks_fun_call/switch_ifelse_etc_no_line_break-out.R b/tests/testthat/line_breaks_fun_call/switch_ifelse_etc_no_line_break-out.R index e6cfeee64..f43cd21f8 100644 --- a/tests/testthat/line_breaks_fun_call/switch_ifelse_etc_no_line_break-out.R +++ b/tests/testthat/line_breaks_fun_call/switch_ifelse_etc_no_line_break-out.R @@ -16,7 +16,6 @@ switch( # ) - switch(x, a = 2, # y = 3 diff --git a/tests/testthat/line_breaks_fun_call/token_dependent_mixed-out.R b/tests/testthat/line_breaks_fun_call/token_dependent_mixed-out.R index d588f1ff0..1bd68278f 100644 --- a/tests/testthat/line_breaks_fun_call/token_dependent_mixed-out.R +++ b/tests/testthat/line_breaks_fun_call/token_dependent_mixed-out.R @@ -16,7 +16,6 @@ call(call( )) - # no more barcket on same line -> call(call( 3, 4 diff --git a/tests/testthat/parse_comments/with_indention-out.R b/tests/testthat/parse_comments/with_indention-out.R index 5854b9515..526802374 100644 --- a/tests/testthat/parse_comments/with_indention-out.R +++ b/tests/testthat/parse_comments/with_indention-out.R @@ -18,8 +18,6 @@ call( # new comment - - a() # I think it gets boring # new_line here diff --git a/tests/testthat/roxygen-examples-complete/13-empty-lines-out.R b/tests/testthat/roxygen-examples-complete/13-empty-lines-out.R index a2f6f567b..460600158 100644 --- a/tests/testthat/roxygen-examples-complete/13-empty-lines-out.R +++ b/tests/testthat/roxygen-examples-complete/13-empty-lines-out.R @@ -9,8 +9,6 @@ #' # two #' #' -#' -#' #' ( #' # more #' a <- 3 diff --git a/tests/testthat/roxygen-examples-complete/26-empty-trailing-lines-out.R b/tests/testthat/roxygen-examples-complete/26-empty-trailing-lines-out.R index f85ff9e76..dc44475aa 100644 --- a/tests/testthat/roxygen-examples-complete/26-empty-trailing-lines-out.R +++ b/tests/testthat/roxygen-examples-complete/26-empty-trailing-lines-out.R @@ -24,7 +24,6 @@ NULL NULL - #' this #' #' empty line after example diff --git a/tests/testthat/test-transformers-drop.R b/tests/testthat/test-transformers-drop.R index 77ccff008..6d7dc099a 100644 --- a/tests/testthat/test-transformers-drop.R +++ b/tests/testthat/test-transformers-drop.R @@ -72,6 +72,7 @@ test_that("tidyverse transformers are correctly dropped", { names_line_break <- c( "remove_empty_lines_after_opening_and_before_closing_braces", + "reduce_extra_blank_lines_between_scopes", "set_line_break_around_comma_and_or", "set_line_break_after_assignment", "set_line_break_after_opening_if_call_is_multi_line", diff --git a/tests/testthat/token_adding_removing/mixed_token-out.R b/tests/testthat/token_adding_removing/mixed_token-out.R index e80aafb4d..068ab64ef 100644 --- a/tests/testthat/token_adding_removing/mixed_token-out.R +++ b/tests/testthat/token_adding_removing/mixed_token-out.R @@ -14,7 +14,6 @@ d 'text with "quotes"' - # adding brackets in pipes a %>% b() %>% From 86daefab8545b58e098192d8cdf181674118ac43 Mon Sep 17 00:00:00 2001 From: "github-actions[bot]" Date: Thu, 28 Nov 2024 19:23:42 +0000 Subject: [PATCH 02/15] pre-commit --- R/rules-line-breaks.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 1e834ab77..2bc121446 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -455,7 +455,7 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { #' @keywords internal reduce_extra_blank_lines_between_scopes <- function(pd_flat, allowed_blank_lines = 2L) { # Calculate the maximum allowed lag_newlines - max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token + max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token # Identify positions where lag_newlines exceed the maximum allowed idx <- which(pd_flat$lag_newlines > max_lag_newlines) From 287c7563ebb7c378ada47b9ce8dc3a3982822fc9 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Thu, 28 Nov 2024 21:20:55 +0100 Subject: [PATCH 03/15] fix --- R/rules-line-breaks.R | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 2bc121446..41da4c523 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -457,11 +457,19 @@ reduce_extra_blank_lines_between_scopes <- function(pd_flat, allowed_blank_lines # Calculate the maximum allowed lag_newlines max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token - # Identify positions where lag_newlines exceed the maximum allowed - idx <- which(pd_flat$lag_newlines > max_lag_newlines) + # Create a copy of lag_newlines to track modifications + modified_lag_newlines <- pd_flat$lag_newlines - # Reduce lag_newlines to the maximum allowed at those positions - pd_flat$lag_newlines[idx] <- max_lag_newlines + # Iterate through the dataframe to reduce consecutive blank lines + for (i in seq_along(modified_lag_newlines)) { + if (modified_lag_newlines[i] > max_lag_newlines) { + modified_lag_newlines[i] <- max_lag_newlines + } + } + + # Update the original data frame + pd_flat$lag_newlines <- modified_lag_newlines return(pd_flat) } + From 2ed01970c0c395e936cbbf9355926405deead00f Mon Sep 17 00:00:00 2001 From: "github-actions[bot]" Date: Thu, 28 Nov 2024 20:24:21 +0000 Subject: [PATCH 04/15] pre-commit --- R/rules-line-breaks.R | 1 - 1 file changed, 1 deletion(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 41da4c523..561914593 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -472,4 +472,3 @@ reduce_extra_blank_lines_between_scopes <- function(pd_flat, allowed_blank_lines return(pd_flat) } - From 23eb8a3fb6d88067bc217bef616c90dc1581d082 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Thu, 28 Nov 2024 21:36:00 +0100 Subject: [PATCH 05/15] add tests --- tests/testthat/line_breaks_and_other/curly-in.R | 9 +++++++++ tests/testthat/line_breaks_and_other/curly-out.R | 6 ++++++ .../line_breaks_and_other/pipe_and_comment-in.R | 9 +++++++++ .../line_breaks_and_other/pipe_and_comment-out.R | 6 ++++++ .../line_breaks_fun_call/blank-non-strict-in.R | 4 ++++ .../line_breaks_fun_call/blank-non-strict-out.R | 1 + .../30-multiple-empty-lines-between-in.R | 16 ++++++++++++++++ .../30-multiple-empty-lines-between-out.R | 13 +++++++++++++ .../testthat/test-roxygen-examples-complete-30.R | 5 +++++ 9 files changed, 69 insertions(+) create mode 100644 tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-in.R create mode 100644 tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-out.R create mode 100644 tests/testthat/test-roxygen-examples-complete-30.R diff --git a/tests/testthat/line_breaks_and_other/curly-in.R b/tests/testthat/line_breaks_and_other/curly-in.R index 8da4db732..31e6fc468 100644 --- a/tests/testthat/line_breaks_and_other/curly-in.R +++ b/tests/testthat/line_breaks_and_other/curly-in.R @@ -59,3 +59,12 @@ while (TRUE){ while (TRUE){# } + + +for (i in 1:10) {} + + + + + +while (TRUE) {} diff --git a/tests/testthat/line_breaks_and_other/curly-out.R b/tests/testthat/line_breaks_and_other/curly-out.R index 22730a44b..753c2a853 100644 --- a/tests/testthat/line_breaks_and_other/curly-out.R +++ b/tests/testthat/line_breaks_and_other/curly-out.R @@ -53,3 +53,9 @@ while (TRUE) { while (TRUE) { # } + + +for (i in 1:10) {} + + +while (TRUE) {} diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R index f0dcfb1d5..6f3ca4fb4 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R @@ -1,2 +1,11 @@ 1:10 %>% # sum sum() + + +f %>% g() + + + + + +h %>% i() diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R index f0dcfb1d5..bad0b84a2 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R @@ -1,2 +1,8 @@ 1:10 %>% # sum sum() + + +f %>% g() + + +h %>% i() diff --git a/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R b/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R index 21225f5f8..cf1631c36 100644 --- a/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R +++ b/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R @@ -10,6 +10,10 @@ call( 1 ) + + + + call( x = 2, 1, diff --git a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R index 02330a9ec..024a4c205 100644 --- a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R +++ b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R @@ -8,6 +8,7 @@ call( 1 ) + call( x = 2, 1, diff --git a/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-in.R b/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-in.R new file mode 100644 index 000000000..880595599 --- /dev/null +++ b/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-in.R @@ -0,0 +1,16 @@ +#' Empty line in examples +#' +#' @examples +1 + + + + + + +#' Empty line in examples +#' +#' @examples +#' \dontrun{ +#' } +2 diff --git a/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-out.R b/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-out.R new file mode 100644 index 000000000..8871734b8 --- /dev/null +++ b/tests/testthat/roxygen-examples-complete/30-multiple-empty-lines-between-out.R @@ -0,0 +1,13 @@ +#' Empty line in examples +#' +#' @examples +1 + + +#' Empty line in examples +#' +#' @examples +#' \dontrun{ +#' +#' } +2 diff --git a/tests/testthat/test-roxygen-examples-complete-30.R b/tests/testthat/test-roxygen-examples-complete-30.R new file mode 100644 index 000000000..f81bab588 --- /dev/null +++ b/tests/testthat/test-roxygen-examples-complete-30.R @@ -0,0 +1,5 @@ +# NB: DO NOT EDIT. Auto-generated by ./tests/dev/generate_roxygen_tests.R. + +test_that("analogous to test-roxygen-examples-complete: 30", { + expect_warning(test_collection("roxygen-examples-complete", "^30-", transformer = style_text), NA) +}) From 1166e3b7cb357f35c26b4d4c4751dd9a47e284d8 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Thu, 28 Nov 2024 21:42:10 +0100 Subject: [PATCH 06/15] update precommit --- .pre-commit-config.yaml | 4 ++-- man/reduce_extra_blank_lines_between_scopes.Rd | 17 +++++++++++++++++ 2 files changed, 19 insertions(+), 2 deletions(-) create mode 100644 man/reduce_extra_blank_lines_between_scopes.Rd diff --git a/.pre-commit-config.yaml b/.pre-commit-config.yaml index 4f34c10b7..0ad306e94 100644 --- a/.pre-commit-config.yaml +++ b/.pre-commit-config.yaml @@ -1,12 +1,12 @@ # All available hooks: https://pre-commit.com/hooks.html # R specific hooks: https://github.com/lorenzwalthert/precommit -default_stages: [commit] +default_stages: [pre-commit] default_language_version: python: python3 repos: - repo: https://github.com/lorenzwalthert/precommit - rev: v0.4.2 + rev: v0.4.3.9003 hooks: - id: style-files args: diff --git a/man/reduce_extra_blank_lines_between_scopes.Rd b/man/reduce_extra_blank_lines_between_scopes.Rd new file mode 100644 index 000000000..37a7a44bc --- /dev/null +++ b/man/reduce_extra_blank_lines_between_scopes.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/rules-line-breaks.R +\name{reduce_extra_blank_lines_between_scopes} +\alias{reduce_extra_blank_lines_between_scopes} +\title{Reduce multiple blank lines to a maximum number of allowed blank lines} +\usage{ +reduce_extra_blank_lines_between_scopes(pd_flat, allowed_blank_lines = 2L) +} +\arguments{ +\item{pd_flat}{A flat parse table.} + +\item{allowed_blank_lines}{The maximum number of allowed blank lines between code elements. Default is \code{2L}.} +} +\description{ +Reduce multiple blank lines to a maximum number of allowed blank lines +} +\keyword{internal} From a2014dc876287a20fddbd8aa344c6f89dec5ceb9 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Sat, 30 Nov 2024 20:27:37 +0100 Subject: [PATCH 07/15] address review feedback --- R/rules-line-breaks.R | 25 +++++-------------- R/style-guides.R | 3 ++- ...reduce_extra_blank_lines_between_scopes.Rd | 17 ------------- .../pipe_and_comment-in.R | 11 ++++++++ .../pipe_and_comment-out.R | 6 +++++ .../blank-non-strict-out.R | 3 +++ 6 files changed, 28 insertions(+), 37 deletions(-) delete mode 100644 man/reduce_extra_blank_lines_between_scopes.Rd diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 561914593..e29c8f603 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -449,26 +449,13 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { } -#' Reduce multiple blank lines to a maximum number of allowed blank lines -#' @param pd_flat A flat parse table. -#' @param allowed_blank_lines The maximum number of allowed blank lines between code elements. Default is `2L`. -#' @keywords internal -reduce_extra_blank_lines_between_scopes <- function(pd_flat, allowed_blank_lines = 2L) { +reduce_extra_blank_lines_between_scopes <- function(pd, allowed_blank_lines = 2L) { # Calculate the maximum allowed lag_newlines - max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token - - # Create a copy of lag_newlines to track modifications - modified_lag_newlines <- pd_flat$lag_newlines + max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token - # Iterate through the dataframe to reduce consecutive blank lines - for (i in seq_along(modified_lag_newlines)) { - if (modified_lag_newlines[i] > max_lag_newlines) { - modified_lag_newlines[i] <- max_lag_newlines - } - } + # cap lag_newlines at max_lag_newlines + pd$lag_newlines <- pmin(pd$lag_newlines, max_lag_newlines) - # Update the original data frame - pd_flat$lag_newlines <- modified_lag_newlines - - return(pd_flat) + pd } + diff --git a/R/style-guides.R b/R/style-guides.R index c61392d1f..b1fad6bc7 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -139,7 +139,8 @@ tidyverse_style <- function(scope = "tokens", if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = if (strict) remove_line_breaks_in_fun_dec, - reduce_extra_blank_lines_between_scopes = reduce_extra_blank_lines_between_scopes, + reduce_extra_blank_lines_between_scopes = + if (strict) reduce_extra_blank_lines_between_scopes, style_line_break_around_curly = partial( style_line_break_around_curly, strict diff --git a/man/reduce_extra_blank_lines_between_scopes.Rd b/man/reduce_extra_blank_lines_between_scopes.Rd deleted file mode 100644 index 37a7a44bc..000000000 --- a/man/reduce_extra_blank_lines_between_scopes.Rd +++ /dev/null @@ -1,17 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/rules-line-breaks.R -\name{reduce_extra_blank_lines_between_scopes} -\alias{reduce_extra_blank_lines_between_scopes} -\title{Reduce multiple blank lines to a maximum number of allowed blank lines} -\usage{ -reduce_extra_blank_lines_between_scopes(pd_flat, allowed_blank_lines = 2L) -} -\arguments{ -\item{pd_flat}{A flat parse table.} - -\item{allowed_blank_lines}{The maximum number of allowed blank lines between code elements. Default is \code{2L}.} -} -\description{ -Reduce multiple blank lines to a maximum number of allowed blank lines -} -\keyword{internal} diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R index 6f3ca4fb4..43970b285 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R @@ -9,3 +9,14 @@ f %>% g() h %>% i() + + + + + +# some comment + + + + +j %>% k() diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R index bad0b84a2..ed19d1149 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R @@ -6,3 +6,9 @@ f %>% g() h %>% i() + + +# some comment + + +j %>% k() diff --git a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R index 024a4c205..9579dbf4d 100644 --- a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R +++ b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R @@ -9,6 +9,9 @@ call( ) + + + call( x = 2, 1, From 35cd8a927b14d840d313cc7360fe9789880db855 Mon Sep 17 00:00:00 2001 From: "github-actions[bot]" Date: Sat, 30 Nov 2024 19:29:10 +0000 Subject: [PATCH 08/15] pre-commit --- R/rules-line-breaks.R | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index e29c8f603..4ae18b760 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -451,11 +451,10 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { reduce_extra_blank_lines_between_scopes <- function(pd, allowed_blank_lines = 2L) { # Calculate the maximum allowed lag_newlines - max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token + max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token # cap lag_newlines at max_lag_newlines pd$lag_newlines <- pmin(pd$lag_newlines, max_lag_newlines) pd } - From 5705339efe2a48d6d2cdaea697be4e399bd97228 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Sat, 30 Nov 2024 20:33:21 +0100 Subject: [PATCH 09/15] another test --- tests/testthat/line_breaks_and_other/ggplot2-in.R | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/testthat/line_breaks_and_other/ggplot2-in.R b/tests/testthat/line_breaks_and_other/ggplot2-in.R index c767dca7a..c9c224cec 100644 --- a/tests/testthat/line_breaks_and_other/ggplot2-in.R +++ b/tests/testthat/line_breaks_and_other/ggplot2-in.R @@ -26,6 +26,7 @@ ggplot(data = mtcars, mapping = aes(x = mpg, y = vs)) + ggplot(data = mtcars, mapping = aes(x = mpg, y = vs)) + ggplot2::geom_point() + g() # comment + # add when comment ggplot(data = mtcars, mapping = aes(x = mpg, y = vs)) + ggplot2::geom_point() + g() + geom_oint() # comment From ab6cb648791050ce6792285c6cb6fd4acba762e2 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Sat, 30 Nov 2024 23:14:48 +0100 Subject: [PATCH 10/15] address feedback --- R/rules-line-breaks.R | 9 ++------- R/style-guides.R | 4 ++-- tests/testthat/test-transformers-drop.R | 2 +- 3 files changed, 5 insertions(+), 10 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 4ae18b760..d1c4458f5 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -449,12 +449,7 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { } -reduce_extra_blank_lines_between_scopes <- function(pd, allowed_blank_lines = 2L) { - # Calculate the maximum allowed lag_newlines - max_lag_newlines <- allowed_blank_lines + 1L # +1 accounts for the line with the previous token - - # cap lag_newlines at max_lag_newlines - pd$lag_newlines <- pmin(pd$lag_newlines, max_lag_newlines) - +reduce_extra_blank_lines_between_top_level_exprs <- function(pd, allowed_blank_lines = 2L) { + pd$lag_newlines <- pmin(pd$lag_newlines, allowed_blank_lines + 1L) pd } diff --git a/R/style-guides.R b/R/style-guides.R index b1fad6bc7..f73fe8a0e 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -139,8 +139,8 @@ tidyverse_style <- function(scope = "tokens", if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = if (strict) remove_line_breaks_in_fun_dec, - reduce_extra_blank_lines_between_scopes = - if (strict) reduce_extra_blank_lines_between_scopes, + reduce_extra_blank_lines_between_top_level_exprs = + if (strict) reduce_extra_blank_lines_between_top_level_exprs, style_line_break_around_curly = partial( style_line_break_around_curly, strict diff --git a/tests/testthat/test-transformers-drop.R b/tests/testthat/test-transformers-drop.R index 6d7dc099a..659baa18d 100644 --- a/tests/testthat/test-transformers-drop.R +++ b/tests/testthat/test-transformers-drop.R @@ -72,7 +72,7 @@ test_that("tidyverse transformers are correctly dropped", { names_line_break <- c( "remove_empty_lines_after_opening_and_before_closing_braces", - "reduce_extra_blank_lines_between_scopes", + "reduce_extra_blank_lines_between_top_level_exprs", "set_line_break_around_comma_and_or", "set_line_break_after_assignment", "set_line_break_after_opening_if_call_is_multi_line", From 7dc83bade493a6d481004871dab7639b95991aec Mon Sep 17 00:00:00 2001 From: Lorenz Walthert Date: Mon, 2 Dec 2024 10:08:55 +0100 Subject: [PATCH 11/15] make name of transformer more similar to existing ones --- R/rules-line-breaks.R | 2 +- R/style-guides.R | 4 ++-- tests/testthat/test-transformers-drop.R | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index d1c4458f5..a02177e5e 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -449,7 +449,7 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { } -reduce_extra_blank_lines_between_top_level_exprs <- function(pd, allowed_blank_lines = 2L) { +set_line_breaks_between_top_level_exprs <- function(pd, allowed_blank_lines = 2L) { pd$lag_newlines <- pmin(pd$lag_newlines, allowed_blank_lines + 1L) pd } diff --git a/R/style-guides.R b/R/style-guides.R index f73fe8a0e..b11ff613c 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -139,8 +139,8 @@ tidyverse_style <- function(scope = "tokens", if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = if (strict) remove_line_breaks_in_fun_dec, - reduce_extra_blank_lines_between_top_level_exprs = - if (strict) reduce_extra_blank_lines_between_top_level_exprs, + set_line_breaks_between_top_level_exprs = + if (strict) set_line_breaks_between_top_level_exprs , style_line_break_around_curly = partial( style_line_break_around_curly, strict diff --git a/tests/testthat/test-transformers-drop.R b/tests/testthat/test-transformers-drop.R index 659baa18d..dfd51afda 100644 --- a/tests/testthat/test-transformers-drop.R +++ b/tests/testthat/test-transformers-drop.R @@ -72,7 +72,7 @@ test_that("tidyverse transformers are correctly dropped", { names_line_break <- c( "remove_empty_lines_after_opening_and_before_closing_braces", - "reduce_extra_blank_lines_between_top_level_exprs", + "set_line_breaks_between_top_level_exprs ", "set_line_break_around_comma_and_or", "set_line_break_after_assignment", "set_line_break_after_opening_if_call_is_multi_line", From a59d4bbdafa37089e38a5c1c885ad92a133ea267 Mon Sep 17 00:00:00 2001 From: "github-actions[bot]" Date: Mon, 2 Dec 2024 09:10:41 +0000 Subject: [PATCH 12/15] pre-commit --- R/rules-line-breaks.R | 2 +- R/style-guides.R | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index a02177e5e..5a007bdff 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -449,7 +449,7 @@ remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) { } -set_line_breaks_between_top_level_exprs <- function(pd, allowed_blank_lines = 2L) { +set_line_breaks_between_top_level_exprs <- function(pd, allowed_blank_lines = 2L) { pd$lag_newlines <- pmin(pd$lag_newlines, allowed_blank_lines + 1L) pd } diff --git a/R/style-guides.R b/R/style-guides.R index b11ff613c..93ea89dd2 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -139,8 +139,8 @@ tidyverse_style <- function(scope = "tokens", if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = if (strict) remove_line_breaks_in_fun_dec, - set_line_breaks_between_top_level_exprs = - if (strict) set_line_breaks_between_top_level_exprs , + set_line_breaks_between_top_level_exprs = + if (strict) set_line_breaks_between_top_level_exprs, style_line_break_around_curly = partial( style_line_break_around_curly, strict From e843fd5dc65f5fb06348dbcfbf2c077524e1e8a1 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Tue, 3 Dec 2024 17:31:16 +0300 Subject: [PATCH 13/15] create a new test collection instead of modifying existing tests --- .../testthat/line_breaks_and_other/curly-in.R | 9 ------ .../line_breaks_and_other/curly-out.R | 6 ---- .../pipe_and_comment-in.R | 20 ------------- .../pipe_and_comment-out.R | 12 -------- .../blank-non-strict-in.R | 4 --- .../blank-non-strict-out.R | 4 --- .../line_breaks_top_level_exprs/braces-in.R | 16 ++++++++++ .../line_breaks_top_level_exprs/braces-out.R | 11 +++++++ .../conditionals-in.R | 20 +++++++++++++ .../conditionals-out.R | 11 +++++++ .../function_defs_and_calls-in.R | 23 ++++++++++++++ .../function_defs_and_calls-out.R | 12 ++++++++ .../non_strict-in.R | 23 ++++++++++++++ .../non_strict-out.R | 12 ++++++++ .../piped_chains-in.R | 21 +++++++++++++ .../piped_chains-out.R | 10 +++++++ .../test-line_breaks_top_level_exprs.R | 30 +++++++++++++++++++ tests/testthat/test-transformers-drop.R | 2 +- 18 files changed, 190 insertions(+), 56 deletions(-) create mode 100644 tests/testthat/line_breaks_top_level_exprs/braces-in.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/braces-out.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/conditionals-in.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/conditionals-out.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-in.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-out.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/non_strict-in.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/non_strict-out.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/piped_chains-in.R create mode 100644 tests/testthat/line_breaks_top_level_exprs/piped_chains-out.R create mode 100644 tests/testthat/test-line_breaks_top_level_exprs.R diff --git a/tests/testthat/line_breaks_and_other/curly-in.R b/tests/testthat/line_breaks_and_other/curly-in.R index 31e6fc468..8da4db732 100644 --- a/tests/testthat/line_breaks_and_other/curly-in.R +++ b/tests/testthat/line_breaks_and_other/curly-in.R @@ -59,12 +59,3 @@ while (TRUE){ while (TRUE){# } - - -for (i in 1:10) {} - - - - - -while (TRUE) {} diff --git a/tests/testthat/line_breaks_and_other/curly-out.R b/tests/testthat/line_breaks_and_other/curly-out.R index 753c2a853..22730a44b 100644 --- a/tests/testthat/line_breaks_and_other/curly-out.R +++ b/tests/testthat/line_breaks_and_other/curly-out.R @@ -53,9 +53,3 @@ while (TRUE) { while (TRUE) { # } - - -for (i in 1:10) {} - - -while (TRUE) {} diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R index 43970b285..f0dcfb1d5 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-in.R @@ -1,22 +1,2 @@ 1:10 %>% # sum sum() - - -f %>% g() - - - - - -h %>% i() - - - - - -# some comment - - - - -j %>% k() diff --git a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R index ed19d1149..f0dcfb1d5 100644 --- a/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R +++ b/tests/testthat/line_breaks_and_other/pipe_and_comment-out.R @@ -1,14 +1,2 @@ 1:10 %>% # sum sum() - - -f %>% g() - - -h %>% i() - - -# some comment - - -j %>% k() diff --git a/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R b/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R index cf1631c36..21225f5f8 100644 --- a/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R +++ b/tests/testthat/line_breaks_fun_call/blank-non-strict-in.R @@ -10,10 +10,6 @@ call( 1 ) - - - - call( x = 2, 1, diff --git a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R index 9579dbf4d..02330a9ec 100644 --- a/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R +++ b/tests/testthat/line_breaks_fun_call/blank-non-strict-out.R @@ -8,10 +8,6 @@ call( 1 ) - - - - call( x = 2, 1, diff --git a/tests/testthat/line_breaks_top_level_exprs/braces-in.R b/tests/testthat/line_breaks_top_level_exprs/braces-in.R new file mode 100644 index 000000000..d504e6413 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/braces-in.R @@ -0,0 +1,16 @@ +{ + 1 + 1 +} + + + + + +### some comment + + + + +{ + NULL +} diff --git a/tests/testthat/line_breaks_top_level_exprs/braces-out.R b/tests/testthat/line_breaks_top_level_exprs/braces-out.R new file mode 100644 index 000000000..9fd7a480d --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/braces-out.R @@ -0,0 +1,11 @@ +{ + 1 + 1 +} + + +### some comment + + +{ + NULL +} diff --git a/tests/testthat/line_breaks_top_level_exprs/conditionals-in.R b/tests/testthat/line_breaks_top_level_exprs/conditionals-in.R new file mode 100644 index 000000000..37e07e57f --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/conditionals-in.R @@ -0,0 +1,20 @@ +for (i in 1:10) {} + + + + + + +# some comment + + + + + +while (TRUE) {} + + + + +# some comment +if (TRUE) NULL diff --git a/tests/testthat/line_breaks_top_level_exprs/conditionals-out.R b/tests/testthat/line_breaks_top_level_exprs/conditionals-out.R new file mode 100644 index 000000000..54104e290 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/conditionals-out.R @@ -0,0 +1,11 @@ +for (i in 1:10) {} + + +# some comment + + +while (TRUE) {} + + +# some comment +if (TRUE) NULL diff --git a/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-in.R b/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-in.R new file mode 100644 index 000000000..4a18af903 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-in.R @@ -0,0 +1,23 @@ +f <- function() NULL + + + + + + + + +g <- function() NULL + + + + +f() + +# comment + + + + + +g() diff --git a/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-out.R b/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-out.R new file mode 100644 index 000000000..741c47309 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/function_defs_and_calls-out.R @@ -0,0 +1,12 @@ +f <- function() NULL + + +g <- function() NULL + + +f() + +# comment + + +g() diff --git a/tests/testthat/line_breaks_top_level_exprs/non_strict-in.R b/tests/testthat/line_breaks_top_level_exprs/non_strict-in.R new file mode 100644 index 000000000..4a18af903 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/non_strict-in.R @@ -0,0 +1,23 @@ +f <- function() NULL + + + + + + + + +g <- function() NULL + + + + +f() + +# comment + + + + + +g() diff --git a/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R b/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R new file mode 100644 index 000000000..741c47309 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R @@ -0,0 +1,12 @@ +f <- function() NULL + + +g <- function() NULL + + +f() + +# comment + + +g() diff --git a/tests/testthat/line_breaks_top_level_exprs/piped_chains-in.R b/tests/testthat/line_breaks_top_level_exprs/piped_chains-in.R new file mode 100644 index 000000000..75a3abee2 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/piped_chains-in.R @@ -0,0 +1,21 @@ + + +f %>% g() + + + + + + +h %>% i() + + + + + +# some comment + + + + +j %>% k() diff --git a/tests/testthat/line_breaks_top_level_exprs/piped_chains-out.R b/tests/testthat/line_breaks_top_level_exprs/piped_chains-out.R new file mode 100644 index 000000000..b424cbba1 --- /dev/null +++ b/tests/testthat/line_breaks_top_level_exprs/piped_chains-out.R @@ -0,0 +1,10 @@ +f %>% g() + + +h %>% i() + + +# some comment + + +j %>% k() diff --git a/tests/testthat/test-line_breaks_top_level_exprs.R b/tests/testthat/test-line_breaks_top_level_exprs.R new file mode 100644 index 000000000..dd8c95da8 --- /dev/null +++ b/tests/testthat/test-line_breaks_top_level_exprs.R @@ -0,0 +1,30 @@ +test_that("extra line breaks between conditional statements are removed", { + expect_no_warning( + test_collection("line_breaks_top_level_exprs", "conditionals", transformer = style_text) + ) +}) + +test_that("extra line breaks between function and definitions and calls are removed", { + expect_no_warning( + test_collection("line_breaks_top_level_exprs", "function_defs_and_calls", transformer = style_text) + ) +}) + +test_that("extra line breaks between piped chains are removed", { + expect_no_warning( + test_collection("line_breaks_top_level_exprs", "piped_chains", transformer = style_text) + ) +}) + +test_that("extra line breaks between braced expressions are removed", { + expect_no_warning( + test_collection("line_breaks_top_level_exprs", "braces", transformer = style_text) + ) +}) + +test_that("extra line breaks are not removed in non-strict mode", { + expect_no_warning( + test_collection("line_breaks_top_level_exprs", "non_strict", transformer = style_text) + ) +}) + diff --git a/tests/testthat/test-transformers-drop.R b/tests/testthat/test-transformers-drop.R index dfd51afda..ad10908f5 100644 --- a/tests/testthat/test-transformers-drop.R +++ b/tests/testthat/test-transformers-drop.R @@ -72,7 +72,7 @@ test_that("tidyverse transformers are correctly dropped", { names_line_break <- c( "remove_empty_lines_after_opening_and_before_closing_braces", - "set_line_breaks_between_top_level_exprs ", + "set_line_breaks_between_top_level_exprs", "set_line_break_around_comma_and_or", "set_line_break_after_assignment", "set_line_break_after_opening_if_call_is_multi_line", From 127588acff38389a4374b8fffe32404cf2bb8199 Mon Sep 17 00:00:00 2001 From: "github-actions[bot]" Date: Tue, 3 Dec 2024 14:32:58 +0000 Subject: [PATCH 14/15] pre-commit --- tests/testthat/test-line_breaks_top_level_exprs.R | 1 - 1 file changed, 1 deletion(-) diff --git a/tests/testthat/test-line_breaks_top_level_exprs.R b/tests/testthat/test-line_breaks_top_level_exprs.R index dd8c95da8..d3a834ea1 100644 --- a/tests/testthat/test-line_breaks_top_level_exprs.R +++ b/tests/testthat/test-line_breaks_top_level_exprs.R @@ -27,4 +27,3 @@ test_that("extra line breaks are not removed in non-strict mode", { test_collection("line_breaks_top_level_exprs", "non_strict", transformer = style_text) ) }) - From 784803915e31c958a06a434f714b6e082bc9a865 Mon Sep 17 00:00:00 2001 From: Indrajeet Patil Date: Tue, 3 Dec 2024 17:34:16 +0300 Subject: [PATCH 15/15] correct non-strict mode test --- .../line_breaks_top_level_exprs/non_strict-out.R | 11 +++++++++++ tests/testthat/test-line_breaks_top_level_exprs.R | 2 +- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R b/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R index 741c47309..4a18af903 100644 --- a/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R +++ b/tests/testthat/line_breaks_top_level_exprs/non_strict-out.R @@ -1,12 +1,23 @@ f <- function() NULL + + + + + + g <- function() NULL + + f() # comment + + + g() diff --git a/tests/testthat/test-line_breaks_top_level_exprs.R b/tests/testthat/test-line_breaks_top_level_exprs.R index dd8c95da8..691c69d30 100644 --- a/tests/testthat/test-line_breaks_top_level_exprs.R +++ b/tests/testthat/test-line_breaks_top_level_exprs.R @@ -24,7 +24,7 @@ test_that("extra line breaks between braced expressions are removed", { test_that("extra line breaks are not removed in non-strict mode", { expect_no_warning( - test_collection("line_breaks_top_level_exprs", "non_strict", transformer = style_text) + test_collection("line_breaks_top_level_exprs", "non_strict", transformer = style_text, strict = FALSE) ) })