Skip to content

Commit

Permalink
ignore mulit-line for / while condition without braces for strict = F…
Browse files Browse the repository at this point in the history
…ALSE
  • Loading branch information
lorenzwalthert committed Aug 5, 2019
1 parent d718c49 commit 5f1be90
Show file tree
Hide file tree
Showing 8 changed files with 416 additions and 190 deletions.
12 changes: 2 additions & 10 deletions R/indent.R
Original file line number Diff line number Diff line change
Expand Up @@ -95,16 +95,8 @@ indent_without_paren_for_while_fun <- function(pd, indent_by) {
if (is_curly_expr(pd$child[[nrow]])) {
return(pd)
}
if (pd$token[1] == "FOR") {
is_multi_line <- pd_is_multi_line(
pd$child[[which(pd$token == "forcond")]]
)
} else if (pd$token[1] %in% c("WHILE", "FUNCTION")) {
start <- which(pd$token == "'('")
end <- which(pd$token == "')'")
is_multi_line <- any(pd[seq2(start, end),]$multi_line)
}
if (pd$token[1] %in% tokens && !is_multi_line) {
browser()
if (pd$token[1] %in% tokens) {
other_trigger_tokens <- c(
math_token,
logical_token,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,14 +10,17 @@ if (x)
for (i in 1:3) #
print(i)

# FIXME
for (i in
1:3) #
print(i)

# FIXME
for (i in #
1:3) #
print(i)

# FIXME
for (#
i in #
1:3#
Expand All @@ -36,18 +39,21 @@ while ( # test
x > 3) # another
return(FALSE)

# FIXME
while (
2 > #here
3 #
) #
FALSE

# FIXME
while (
2 > #here
3 #
)
FALSE

# FIXME
while (
2 > #here
3
Expand Down

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -10,19 +10,22 @@ if (x)
for (i in 1:3) #
print(i)

# FIXME
for (i in
1:3) #
print(i)
print(i)

# FIXME
for (i in #
1:3) #
print(i)
print(i)

# FIXME
for ( #
i in #
1:3 #
) #
print(i)
print(i)


while (x > 3) #
Expand All @@ -40,19 +43,19 @@ while (
2 > # here
3 #
) #
FALSE
FALSE

while (
2 > # here
3 #
)
FALSE
FALSE

while (
2 > # here
3
) #
FALSE
FALSE

while ( #
2 >
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
while(x == 2) h(
2
)

while(x == 2) h( # comment
2
)

while(x == 2 &&
2 + 2 == 2) h(
2
)


for(x in 1:22) h(
2
)

for(x in 1:22) h( # comment
2
)

for(k in f(
2:22
)) h(
2
)

for(k in f(
2:22 # comment
)) h(2)

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

Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
while (x == 2) h(
2
)

while (x == 2) h( # comment
2
)

while (x == 2 &&
2 + 2 == 2) h(
2
)


for (x in 1:22) h(
2
)

for (x in 1:22) h( # comment
2
)

for (k in f(
2:22
)) h(
2
)

for (k in f(
2:22 # comment
)) h(2)
3 changes: 3 additions & 0 deletions tests/testthat/test-indention_operators.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,9 @@ test_that("while / for / if without curly brackets", {
expect_warning(test_collection("indention_operators",
"while_for_if_without_curly_non_strict",
transformer = style_text, strict = FALSE), NA)
expect_warning(test_collection("indention_operators",
"while_for_without_curly_same_line_non_strict",
transformer = style_text, strict = FALSE), NA)
})

test_that("function multiline without curly brackets", {
Expand Down

0 comments on commit 5f1be90

Please sign in to comment.