diff --git a/R/expr-is.R b/R/expr-is.R index 8e0225d77..f1021fd06 100644 --- a/R/expr-is.R +++ b/R/expr-is.R @@ -96,7 +96,7 @@ is_subset_expr <- function(pd) { if (is.null(pd) || nrow(pd) == 1) { return(FALSE) } - pd$token[2L] == "'['" + pd$token[2L] %in% subset_token_opening } diff --git a/R/indent.R b/R/indent.R index 17e9f1af5..475291b9c 100644 --- a/R/indent.R +++ b/R/indent.R @@ -87,8 +87,15 @@ indent_without_paren_if_else <- function(pd, indent_by) { #' example in if-else expressions, this is not the case and indenting #' everything between '(' and the penultimate token would result in the wrong #' formatting. +#' @section Handing of `[[`: +#' Since text `[[` has token `"LBB"` and text `]]` is parsed as two independent +#' `]` (see 'Examples'), indention has to stop at the first `]`. +# one token earlier #' @importFrom rlang seq2 #' @keywords internal +#' @examples +#' styler:::parse_text("a[1]") +#' styler:::parse_text("a[[1\n]]") compute_indent_indices <- function(pd, token_opening, token_closing = NULL) { @@ -105,7 +112,8 @@ compute_indent_indices <- function(pd, if (is.null(token_closing)) { stop <- npd } else { - stop <- last(which(pd$token %in% token_closing)[needs_indention]) - 1 + offset <- if (any(pd$token == "LBB")) 2L else 1L + stop <- last(which(pd$token %in% token_closing)[needs_indention]) - offset } seq2(start, stop) diff --git a/R/rules-indention.R b/R/rules-indention.R index e342ae167..e6ac2d5ce 100644 --- a/R/rules-indention.R +++ b/R/rules-indention.R @@ -4,7 +4,7 @@ indent_braces <- function(pd, indent_by) { indent_indices <- compute_indent_indices( pd, - token_opening = c("'('", "'['", "'{'"), + token_opening = c("'('", "'['", "'{'", "LBB"), token_closing = c("')'", "']'", "'}'") ) pd$indent[indent_indices] <- pd$indent[indent_indices] + indent_by diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 46f4e0fa4..705e52a2e 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -128,7 +128,7 @@ set_line_break_around_comma_and_or <- function(pd, strict) { (pd$token %in% ops) & (pd$lag_newlines > 0L) & (pd$token_before != "COMMENT") & - (lag(pd$token) != "'['") + !(lag(pd$token) %in% subset_token_opening) pd$lag_newlines[comma_with_line_break_that_can_be_removed_before] <- 0L pd$lag_newlines[lag(comma_with_line_break_that_can_be_removed_before)] <- 1L @@ -137,7 +137,7 @@ set_line_break_around_comma_and_or <- function(pd, strict) { (pd$token == "EQ_SUB") & (pd$lag_newlines > 0L) & (pd$token_before != "COMMENT") & - (lag(pd$token) != "'['") + !(lag(pd$token) %in% subset_token_opening) ) pd$lag_newlines[comma_with_line_break_that_can_be_moved_two_tokens_left] <- 0L @@ -362,7 +362,12 @@ set_line_break_before_closing_call <- function(pd, except_token_before) { pd$lag_newlines[setdiff(npd, exception)] <- 0L return(pd) } - pd$lag_newlines[npd] <- 1L + idx_non_comment <- previous_non_comment(pd, npd) + if (pd$token[idx_non_comment] == "']'") { + pd$lag_newlines[idx_non_comment] <- 1L + } else { + pd$lag_newlines[npd] <- 1L + } pd } diff --git a/R/token-define.R b/R/token-define.R index 06ae3f792..6a44d95af 100644 --- a/R/token-define.R +++ b/R/token-define.R @@ -70,3 +70,5 @@ op_token <- c( "EQ_SUB", "ELSE", "IN", "EQ_FORMALS" ) + +subset_token_opening <- c("'['", "LBB") diff --git a/man/compute_indent_indices.Rd b/man/compute_indent_indices.Rd index 7538d91f6..ff16421e4 100644 --- a/man/compute_indent_indices.Rd +++ b/man/compute_indent_indices.Rd @@ -34,4 +34,14 @@ example in if-else expressions, this is not the case and indenting everything between '(' and the penultimate token would result in the wrong formatting. } +\section{Handing of \code{[[}}{ + +Since text \code{[[} has token \code{"LBB"} and text \verb{]]} is parsed as two independent +\verb{]} (see 'Examples'), indention has to stop at the first \verb{]}. +} + +\examples{ +styler:::parse_text("a[1]") +styler:::parse_text("a[[1\n]]") +} \keyword{internal} diff --git a/tests/testthat/indention_square_brackets/square_brackets_double_line_break-in.R b/tests/testthat/indention_square_brackets/square_brackets_double_line_break-in.R new file mode 100644 index 000000000..f5a2fc449 --- /dev/null +++ b/tests/testthat/indention_square_brackets/square_brackets_double_line_break-in.R @@ -0,0 +1,22 @@ +a[[b]] + + +a[[ + 2 +] +] + +a[[ + 2 +]] + + +a[[ +2 + ]] + + +a[[ + 2 +] # +] diff --git a/tests/testthat/indention_square_brackets/square_brackets_double_line_break-out.R b/tests/testthat/indention_square_brackets/square_brackets_double_line_break-out.R new file mode 100644 index 000000000..2b5225958 --- /dev/null +++ b/tests/testthat/indention_square_brackets/square_brackets_double_line_break-out.R @@ -0,0 +1,22 @@ +a[[b]] + + +a[[ + 2 +] +] + +a[[ + 2 +]] + + +a[[ + 2 +]] + + +a[[ + 2 + ] # +] diff --git a/tests/testthat/test-square_brackets.R b/tests/testthat/test-square_brackets.R index ccad96f0d..a400c1f30 100644 --- a/tests/testthat/test-square_brackets.R +++ b/tests/testthat/test-square_brackets.R @@ -3,7 +3,6 @@ test_that("square brackets cause indention", { expect_warning(test_collection( "indention_square_brackets", - "square_brackets_line_break", transformer = style_text ), NA) })