Skip to content

Commit

Permalink
Merge pull request #1234 from r-lib/empty-curly
Browse files Browse the repository at this point in the history
empty curly have no spaces around
  • Loading branch information
lorenzwalthert authored Oct 9, 2024
2 parents 08d11e1 + e1455c6 commit faa0558
Show file tree
Hide file tree
Showing 19 changed files with 85 additions and 75 deletions.
5 changes: 2 additions & 3 deletions .pre-commit-config.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,6 @@ repos:
)$
- id: roxygenize
additional_dependencies:
- r-lib/pkgapi
- dplyr
- roxygen2
- rlang
Expand Down Expand Up @@ -102,7 +101,7 @@ repos:
)$
- id: pkgdown
- repo: https://github.com/pre-commit/pre-commit-hooks
rev: v4.6.0
rev: v5.0.0
hooks:
- id: check-added-large-files
args: ["--maxkb=200"]
Expand All @@ -120,7 +119,7 @@ repos:
tests/testthat/_snaps/.*|
)$
- repo: https://github.com/lorenzwalthert/gitignore-tidy
rev: 517cddbf1d8514ddaf43159686617ae65895dc99
rev: 0.1.2
hooks:
- id: tidy-gitignore
- repo: local
Expand Down
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ Roxygen: list(markdown = TRUE, roclets = c( "rd", "namespace", "collate",
if (rlang::is_installed("pkgapi")) "pkgapi::api_roclet" else {
warning("Please install r-lib/pkgapi to make sure the file API is kept
up to date"); NULL}))
RoxygenNote: 7.3.1
RoxygenNote: 7.3.2
Language: en-US
Config/testthat/edition: 3
Config/testthat/parallel: true
Expand Down
24 changes: 15 additions & 9 deletions R/rules-line-breaks.R
Original file line number Diff line number Diff line change
Expand Up @@ -149,15 +149,21 @@ set_line_break_around_comma_and_or <- function(pd, strict) {
}

style_line_break_around_curly <- function(strict, pd) {
if (is_curly_expr(pd) && nrow(pd) > 2L) {
closing_before <- pd$token == "'}'"
opening_before <- (pd$token == "'{'")
to_break <- lag(opening_before, default = FALSE) | closing_before
pd$lag_newlines[to_break] <- ifelse(
pd$token[to_break] == "COMMENT",
pmin(1L, pd$lag_newlines[to_break]),
if (strict) 1L else pmax(1L, pd$lag_newlines[to_break])
)
if (is_curly_expr(pd)) {
n_row <- nrow(pd)
if (n_row > 2L) {
closing_before <- pd$token == "'}'"
opening_before <- (pd$token == "'{'")
to_break <- lag(opening_before, default = FALSE) | closing_before
pd$lag_newlines[to_break] <- ifelse(
pd$token[to_break] == "COMMENT",
pmin(1L, pd$lag_newlines[to_break]),
if (strict) 1L else pmax(1L, pd$lag_newlines[to_break])
)
} else if (n_row == 2L) {
# pd represents {}
pd$lag_newlines[2L] <- 0L
}
} else {
is_else <- pd$token == "ELSE"
if (any(pd$token_before[is_else] == "'}'")) {
Expand Down
7 changes: 6 additions & 1 deletion R/rules-spaces.R
Original file line number Diff line number Diff line change
Expand Up @@ -174,8 +174,9 @@ add_space_after_for_if_while <- function(pd_flat) {

#' @rdname set_line_break_around_curly_curly
#' @keywords internal
set_space_in_curly_curly <- function(pd) {
set_space_in_curly <- function(pd) {
if (is_curly_expr(pd)) {
# curly-curly
after_inner_opening <- pd$token == "'{'" & pd$token_before == "'{'"
before_inner_closing <- lead(pd$token == "'}'" & pd$token_after == "'}'")
is_curly_curly_inner <- any(after_inner_opening, na.rm = TRUE) &&
Expand All @@ -193,6 +194,10 @@ set_space_in_curly_curly <- function(pd) {
pd$spaces[after_outer_opening] <- 0L
pd$spaces[before_outer_closing] <- 0L
}

# empty curly
after_is_empty_curly <- lead(pd$token == "'}'" & pd$token_before == "'{'")
pd$spaces[after_is_empty_curly] <- 0L
}
pd
}
Expand Down
4 changes: 2 additions & 2 deletions R/style-guides.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ tidyverse_style <- function(scope = "tokens",
},
set_space_between_levels = set_space_between_levels,
set_space_between_eq_sub_and_comma = set_space_between_eq_sub_and_comma,
set_space_in_curly_curly = set_space_in_curly_curly
set_space_in_curly = set_space_in_curly
)
}

Expand Down Expand Up @@ -209,7 +209,7 @@ tidyverse_style <- function(scope = "tokens",
start_comments_with_space = "COMMENT",
remove_space_after_unary_pm_nested = c("'+'", "'-'"),
spacing_before_comments = "COMMENT",
set_space_in_curly_curly = c("'{'", "'}'")
set_space_in_curly = c("'{'", "'}'")
),
indention = list(
# indent_braces = c("'('", "'['", "'{'", "')'", "']'", "'}'"),
Expand Down
4 changes: 2 additions & 2 deletions man/set_line_break_around_curly_curly.Rd

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

3 changes: 1 addition & 2 deletions tests/testthat/indention_multiple/edge_strict_mixed-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,5 +23,4 @@
)))


function(x, y, z) {
}
function(x, y, z) {}
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,4 @@ function(a =
f =
d, c =
3, d =
4) {

}
4) {}
28 changes: 7 additions & 21 deletions tests/testthat/line_breaks_and_other/braces-fun-calls2-out.R
Original file line number Diff line number Diff line change
@@ -1,8 +1,6 @@
test(
"x",
{

},
{},
a + b,
{
s(x = sd)
Expand All @@ -11,9 +9,7 @@ test(

test(
"x",
{

},
{},
a + b,
{
s(x = sd)
Expand All @@ -22,9 +18,7 @@ test(

test(
"x",
{

},
{},
a + b,
{
s(x = sd)
Expand All @@ -34,9 +28,7 @@ test(

test(
"x",
{

},
{},
a + b,
{
s(x = sd)
Expand All @@ -45,9 +37,7 @@ test(

test(
"x",
{

}, # h
{}, # h
a + b,
{
s(x = sd)
Expand All @@ -56,9 +46,7 @@ test(

test(
"x",
{

}, # h
{}, # h
a + b,
# k
{
Expand All @@ -68,9 +56,7 @@ test(

test(
"x",
{

},
{},
a + b, # k
{
s(x = sd)
Expand Down
18 changes: 18 additions & 0 deletions tests/testthat/line_breaks_and_other/curly-in.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,3 +41,21 @@ test_that(
# comment
expect_equal(1 + 1, 2)
})


while (TRUE) { }

while (TRUE)
{ }

while (TRUE){

}

while (TRUE){
#
}


while (TRUE){#
}
15 changes: 15 additions & 0 deletions tests/testthat/line_breaks_and_other/curly-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -38,3 +38,18 @@ test_that(
expect_equal(1 + 1, 2)
}
)


while (TRUE) {}

while (TRUE) {}

while (TRUE) {}

while (TRUE) {
#
}


while (TRUE) { #
}
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,7 @@ call(call(
call(call(1,
2))
# multi-line: no indention based on first vall
call(a(b(c({
}))))
call(a(b(c({}))))

call(call(
2),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,7 @@ call(call(
2
))
# multi-line: no indention based on first vall
call(a(b(c({
}))))
call(a(b(c({}))))

call(
call(
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
# A comment
a <- function() {

}
a <- function() {}

#+ chunk-label, opt1=value1
"chunk-content"
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
# random
this(is_a_call(x))
if (x) {
}
if (x) {}
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
# random
this(is_a_call(x))
if (x) {
}
if (x) {}
6 changes: 2 additions & 4 deletions tests/testthat/spacing/round_curly-out.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
a <- function(x) {
}
a <- function(x) {}

if (a) {
3
Expand All @@ -13,5 +12,4 @@ if (x) {
y
} else if (x) {
x
} else {
}
} else {}
12 changes: 4 additions & 8 deletions tests/testthat/strict/non_strict-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,17 +51,13 @@ test <- function() {
call
})

braced("unnamed reduces space", {
})
braced("unnamed reduces space", {})

braced("unnamed adds space space", {
})
braced("unnamed adds space space", {})

braced(named_reduces_space = {
})
braced(named_reduces_space = {})

braced(named_adds_space = {
})
braced(named_adds_space = {})

braced({
empty_removes_space
Expand Down
12 changes: 4 additions & 8 deletions tests/testthat/strict/strict-out.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,17 +34,13 @@ test <- function() {
call
})

braced("unnamed reduces space", {
})
braced("unnamed reduces space", {})

braced("unnamed adds space space", {
})
braced("unnamed adds space space", {})

braced(named_reduces_space = {
})
braced(named_reduces_space = {})

braced(named_adds_space = {
})
braced(named_adds_space = {})

braced({
empty_removes_space
Expand Down

0 comments on commit faa0558

Please sign in to comment.