Skip to content

Commit

Permalink
Merge pull request #1195 from r-lib/f1032-remove-blank-lines-after-an…
Browse files Browse the repository at this point in the history
…d-before-parens

Remove blank lines after opening and before closing braces
  • Loading branch information
IndrajeetPatil authored May 20, 2024
2 parents 4256522 + f9d4ab4 commit 6db6eff
Show file tree
Hide file tree
Showing 28 changed files with 291 additions and 24 deletions.
4 changes: 2 additions & 2 deletions .github/workflows/check-full.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -25,9 +25,9 @@ jobs:
# use 4.1 to check with rtools40's older compiler
- { os: windows-latest, r: "4.1" }

- { os: ubuntu-latest, r: "devel", http-user-agent: "release" }
- { os: ubuntu-latest, r: "devel", locale: "en_US" }
- { os: ubuntu-latest, r: "devel", locale: "en_US", http-user-agent: "release" }
#- { os: ubuntu-latest, r: "release", locale: "zh_CN" }
- { os: ubuntu-latest, r: "release" }
- { os: ubuntu-latest, r: "oldrel-1" }
- { os: ubuntu-latest, r: "oldrel-2" }
- { os: ubuntu-latest, r: "oldrel-3" }
Expand Down
9 changes: 2 additions & 7 deletions .github/workflows/pre-commit.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -24,19 +24,14 @@ jobs:
- uses: actions/checkout@v4
with:
fetch-depth: 0
- name: Install system dependencies
if: runner.os == 'Linux'
run: |
# your system installation code here
# sudo apt-get install -y libcurl4-openssl-dev
- name: Set up Python
uses: actions/setup-python@v5
uses: actions/setup-python@v5.1.0
with:
python-version: "3.9"
architecture: "x64"
- name: Run pre-commit
uses: pre-commit/[email protected]
env:
env:
SKIP: pkgdown
- name: Commit files
if: failure() && startsWith(github.ref, 'refs/heads')
Expand Down
24 changes: 23 additions & 1 deletion R/rules-line-breaks.R
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ remove_line_breaks_in_fun_dec <- function(pd) {
pd
}

#'

add_line_break_after_pipe <- function(pd) {
is_pipe <- pd$token %in% c("SPECIAL-PIPE", "PIPE")
pd$lag_newlines[lag(is_pipe) & pd$lag_newlines > 1L] <- 1L
Expand Down Expand Up @@ -417,3 +417,25 @@ set_line_break_after_ggplot2_plus <- function(pd) {
}
pd
}


remove_empty_lines_after_opening_and_before_closing_braces <- function(pd) {
opening_braces <- c("'('", "'['", "LBB")
closing_braces <- c("')'", "']'")

paren_after <- pd$token %in% opening_braces
if (any(paren_after)) {
pd$lag_newlines[
lag(pd$token %in% opening_braces) & pd$lag_newlines > 1L
] <- 1L
}

paren_before <- pd$token %in% closing_braces
if (any(paren_before)) {
pd$lag_newlines[
pd$token %in% closing_braces & pd$lag_newlines > 1L
] <- 1L
}

pd
}
9 changes: 6 additions & 3 deletions R/rules-spaces.R
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,8 @@ remove_space_after_unary_pm_nested <- function(pd) {
}

remove_space_before_opening_paren <- function(pd_flat) {
paren_after <- pd_flat$token %in% c("'('", "'['", "LBB")
opening_braces <- c("'('", "'['", "LBB")
paren_after <- pd_flat$token %in% opening_braces
if (!any(paren_after)) {
return(pd_flat)
}
Expand All @@ -141,7 +142,8 @@ remove_space_before_opening_paren <- function(pd_flat) {
}

remove_space_after_opening_paren <- function(pd_flat) {
paren_after <- pd_flat$token %in% c("'('", "'['", "LBB")
opening_braces <- c("'('", "'['", "LBB")
paren_after <- pd_flat$token %in% opening_braces
if (!any(paren_after)) {
return(pd_flat)
}
Expand All @@ -150,7 +152,8 @@ remove_space_after_opening_paren <- function(pd_flat) {
}

remove_space_before_closing_paren <- function(pd_flat) {
paren_after <- pd_flat$token %in% c("')'", "']'")
closing_braces <- c("')'", "']'")
paren_after <- pd_flat$token %in% closing_braces
if (!any(paren_after)) {
return(pd_flat)
}
Expand Down
2 changes: 2 additions & 0 deletions R/style-guides.R
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,8 @@ tidyverse_style <- function(scope = "tokens",

line_break_manipulators <- if ("line_breaks" %in% scope) {
list(
remove_empty_lines_after_opening_and_before_closing_braces =
remove_empty_lines_after_opening_and_before_closing_braces,
set_line_break_around_comma_and_or = set_line_break_around_comma_and_or,
set_line_break_after_assignment = set_line_break_after_assignment,
set_line_break_before_curly_opening = set_line_break_before_curly_opening,
Expand Down
10 changes: 10 additions & 0 deletions tests/testthat/indention_curly_brackets/multi_line_curly_only-in.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,3 +2,13 @@
{1 + 3}
{2 + sin(pi)}
}

{

# some additions
{1 + 3}
{2 + sin(pi)}

# nothing to see here

}
Original file line number Diff line number Diff line change
Expand Up @@ -6,3 +6,15 @@
2 + sin(pi)
}
}

{
# some additions
{
1 + 3
}
{
2 + sin(pi)
}

# nothing to see here
}
Original file line number Diff line number Diff line change
Expand Up @@ -8,3 +8,18 @@ a <- function(x, y, z) {
x[i] +1
}
}


if (

require("logspline") &&
require("rstanarm")



) {

NULL


}
Original file line number Diff line number Diff line change
Expand Up @@ -8,3 +8,11 @@ a <- function(x, y, z) {
x[i] + 1
}
}


if (
require("logspline") &&
require("rstanarm")
) {
NULL
}
13 changes: 13 additions & 0 deletions tests/testthat/indention_round_brackets/arithmetic_start-in.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,16 @@
3 + 4
)
)

(

1 +
2 + (
# the space below is intentional

3 + 4
# but the one here isn't


)
)
10 changes: 10 additions & 0 deletions tests/testthat/indention_round_brackets/arithmetic_start-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,13 @@
3 + 4
)
)

(
1 +
2 + (
# the space below is intentional

3 + 4
# but the one here isn't
)
)
13 changes: 13 additions & 0 deletions tests/testthat/indention_round_brackets/multi_line-random-in.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,16 @@ call3(1, 2, 22),
),
144
)

call(

1,
call2(
2, 3,
call3(1, 2, 22),
5

),
144

)
10 changes: 10 additions & 0 deletions tests/testthat/indention_round_brackets/multi_line-random-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,13 @@ call(
),
144
)

call(
1,
call2(
2, 3,
call3(1, 2, 22),
5
),
144
)
Original file line number Diff line number Diff line change
Expand Up @@ -20,3 +20,26 @@ a[[
2
] #
]


a[[

2


]]


a[[

# this comment shouldn't mess
1, c(

1, 2

# neither should this one

)


]]
Original file line number Diff line number Diff line change
Expand Up @@ -20,3 +20,18 @@ a[[
2
] #
]


a[[
2
]]


a[[
# this comment shouldn't mess
1, c(
1, 2

# neither should this one
)
]]
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,14 @@ fac[
]

fac[, `:`(a = c)
]

fac[

, `:`(a = c)



]

x[a ==3 |
Expand All @@ -44,3 +52,36 @@ x[a ==3 &&

x[a ==3 &
b == v,]

x[

# comments above
a ==3 &
b == v,
# or below shouldn't be an issue


]


x[

a,
b


]

x[

# this comment shouldn't be an issue
1, c(

1, 2

# neither should this one

)


]
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,10 @@ fac[

fac[, `:`(a = c)]

fac[
, `:`(a = c)
]

x[a == 3 |
b == v, ]

Expand All @@ -48,3 +52,25 @@ x[a == 3 &&

x[a == 3 &
b == v, ]

x[
# comments above
a == 3 &
b == v,
# or below shouldn't be an issue
]


x[
a,
b
]

x[
# this comment shouldn't be an issue
1, c(
1, 2

# neither should this one
)
]
3 changes: 1 addition & 2 deletions tests/testthat/line_breaks_and_other/assignment-in.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,7 @@ x <-

x <- 3

# FIXME: edge case not working for R < 3.6: Problem: most likely, comment is
# not moved to the right nest with relocate_eq_assign.

x <-
# the culprit

Expand Down
3 changes: 1 addition & 2 deletions tests/testthat/line_breaks_and_other/assignment-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,7 @@ x <-

x <- 3

# FIXME: edge case not working for R < 3.6: Problem: most likely, comment is
# not moved to the right nest with relocate_eq_assign.

x <-
# the culprit

Expand Down
Loading

0 comments on commit 6db6eff

Please sign in to comment.