diff --git a/NEWS.md b/NEWS.md index 2a2ba388a..4dbff9603 100644 --- a/NEWS.md +++ b/NEWS.md @@ -43,6 +43,8 @@ editor_options: (#946). - turned off `styler.print.Vertical` in vignettes so ANSI output of {prettycode} not messing with {pkgdown} (\@IndrajeetPatil, #956, #957). +- Improved code quality by fixing {lintr} warnings (#960). + # styler 1.7.0 diff --git a/R/addins.R b/R/addins.R index 5ed0f53c7..a62074d95 100644 --- a/R/addins.R +++ b/R/addins.R @@ -37,8 +37,9 @@ #' # save after styling when using the Addin #' options(styler.save_after_styling = TRUE) #' # only style with scope = "spaces" when using the Addin +#' val <- "styler::tidyverse_style(scope = 'spaces')" #' options( -#' styler.addins_style_transformer = "styler::tidyverse_style(scope = 'spaces')" +#' styler.addins_style_transformer = val #' ) #' } NULL @@ -130,7 +131,11 @@ style_selection <- function() { base_indention = nchar(gsub("^( *).*", "\\1", text)) ) rstudioapi::modifyRange( - context$selection[[1]]$range, paste0(c(out, if (context$selection[[1]]$range$end[2] == 1) ""), collapse = "\n"), + context$selection[[1]]$range, + paste0(c( + out, + if (context$selection[[1]]$range$end[2] == 1) "" + ), collapse = "\n"), id = context$id ) if (save_after_styling_is_active() == TRUE && context$path != "") { @@ -212,9 +217,9 @@ try_transform_as_r_file <- function(context, transformer) { transformer(context$contents), error = function(e) { preamble_for_unsaved <- paste( - "Styling of unsaved files is only supported for R files with valid code.", - "Please save the file (as .R or .Rmd) and make sure that the R code in it", - "can be parsed. Then, try to style again." + "Styling of unsaved files is only supported for R files with valid ", + "code. Please save the file (as .R or .Rmd) and make sure that the R ", + "code in it can be parsed. Then, try to style again." ) if (context$path == "") { diff --git a/R/communicate.R b/R/communicate.R index 3e50e272d..7c6961b35 100644 --- a/R/communicate.R +++ b/R/communicate.R @@ -25,9 +25,17 @@ communicate_summary <- function(changed, ruler_width) { if (!getOption("styler.quiet", FALSE)) { cli::cat_rule(width = max(40, ruler_width)) cat("Status\tCount\tLegend \n") - cli::cat_bullet("\t", sum(!changed, na.rm = TRUE), "\tFile unchanged.", bullet = "tick") - cli::cat_bullet("\t", sum(changed, na.rm = TRUE), "\tFile changed.", bullet = "info") - cli::cat_bullet(bullet = "cross", "\t", sum(is.na(changed)), "\tStyling threw an error.") + cli::cat_bullet( + "\t", sum(!changed, na.rm = TRUE), "\tFile unchanged.", + bullet = "tick" + ) + cli::cat_bullet( + "\t", sum(changed, na.rm = TRUE), "\tFile changed.", + bullet = "info" + ) + cli::cat_bullet( + bullet = "cross", "\t", sum(is.na(changed)), "\tStyling threw an error." + ) cli::cat_rule(width = max(40, ruler_width)) } } diff --git a/R/detect-alignment-utils.R b/R/detect-alignment-utils.R index fca40631a..e868be4e8 100644 --- a/R/detect-alignment-utils.R +++ b/R/detect-alignment-utils.R @@ -108,9 +108,9 @@ alignment_serialize_column <- function(relevant_pd_by_line, column) { #' @keywords internal alignment_serialize_line <- function(relevant_pd_by_line, column) { # TODO - # better also add lover bound for column. If you already checked up to comma 2, - # you don't need to re-construct text again, just check if text between comma 2 - # and 3 has the same length. + # better also add lover bound for column. If you already checked up to + # comma 2, you don't need to re-construct text again, just check if text + # between comma 2 and 3 has the same length. comma_idx <- which(relevant_pd_by_line$token == "','") n_cols <- length(comma_idx) if (column > n_cols) { diff --git a/R/detect-alignment.R b/R/detect-alignment.R index 264ebcbef..834067935 100644 --- a/R/detect-alignment.R +++ b/R/detect-alignment.R @@ -116,7 +116,8 @@ token_is_on_aligned_line <- function(pd_flat) { # first col has no leading , current_col <- nchar(by_line) - as.integer(column > 1) - # Problem `by_line` counting from comma before column 3, previous_line counting 1 space before ~ + # Problem `by_line` counting from comma before column 3, previous_line + # counting 1 space before ~ if (column > 1) { previous_line <- previous_line[ intersect(names(previous_line), names(by_line)) diff --git a/R/environments.R b/R/environments.R index dd4a36f88..b5ce9e80a 100755 --- a/R/environments.R +++ b/R/environments.R @@ -5,11 +5,11 @@ #' around. Examples are [#187](https://github.com/r-lib/styler/issues/187), #' [#216](https://github.com/r-lib/styler/issues/216), #' [#100](https://github.com/r-lib/styler/issues/100) and others. With -#' [#419](https://github.com/r-lib/styler/issues/419), the structure of the parse -#' data changes and we need to dispatch for older versions. As it is inconvenient -#' to pass a parser version down in the call stack in various places, the -#' environment `env_current` is used to store the current version *globally* -#' but internally. +#' [#419](https://github.com/r-lib/styler/issues/419), the structure of the +#' parse data changes and we need to dispatch for older versions. As it is +#' inconvenient to pass a parser version down in the call stack in various +#' places, the environment `env_current` is used to store the current version +#' *globally* but internally. #' #' We version the parser as follows: #' diff --git a/R/indent.R b/R/indent.R index 52c900d11..9fc773dfc 100644 --- a/R/indent.R +++ b/R/indent.R @@ -8,8 +8,8 @@ #' @keywords internal NULL -#' @describeIn update_indention Is used to indent for and statements and function -#' definitions without parenthesis. +#' @describeIn update_indention Is used to indent for and statements and +#' function definitions without parenthesis. #' @keywords internal indent_without_paren_for_while_fun <- function(pd, indent_by) { tokens <- c("FOR", "WHILE", "FUNCTION") @@ -39,7 +39,9 @@ indent_without_paren_if_else <- function(pd, indent_by) { if (!is_if) { return(pd) } - needs_indention_now <- pd$lag_newlines[next_non_comment(pd, which(pd$token == "')'"))] > 0 + needs_indention_now <- pd$lag_newlines[ + next_non_comment(pd, which(pd$token == "')'")) + ] > 0 if (needs_indention_now) { pd$indent[expr_after_if] <- indent_by @@ -57,7 +59,9 @@ indent_without_paren_if_else <- function(pd, indent_by) { pd$child[[expr_after_else_idx]]$token[1] != "'{'" && pd$child[[expr_after_else_idx]]$token[1] != "IF" - needs_indention_now <- pd$lag_newlines[next_non_comment(pd, which(pd$token == "ELSE"))] > 0 + needs_indention_now <- pd$lag_newlines[ + next_non_comment(pd, which(pd$token == "ELSE")) + ] > 0 if (has_else_without_curly_or_else_chid && needs_indention_now) { pd$indent[seq(else_idx + 1, nrow(pd))] <- indent_by @@ -231,7 +235,8 @@ pd_multi_line <- function(pd) { #' R/rules-spacing.R for tokens at the end of a line since this allows styling #' without touching indention. #' @param pd A parse table. -#' @return A parse table with synchronized `lag_newlines` and `newlines` columns. +#' @return A parse table with synchronized `lag_newlines` and `newlines` +#' columns. #' @seealso choose_indention #' @keywords internal update_newlines <- function(pd) { diff --git a/R/nest.R b/R/nest.R index 3e96f1a2b..09704bc9c 100644 --- a/R/nest.R +++ b/R/nest.R @@ -109,7 +109,8 @@ add_cache_block <- function(pd_nested) { #' @keywords internal drop_cached_children <- function(pd) { if (cache_is_activated()) { - pd_parent_first <- pd[order(pd$line1, pd$col1, -pd$line2, -pd$col2, as.integer(pd$terminal)), ] + order <- order(pd$line1, pd$col1, -pd$line2, -pd$col2, as.integer(pd$terminal)) + pd_parent_first <- pd[order, ] pos_ids_to_keep <- pd_parent_first %>% split(cumsum(pd_parent_first$parent == 0)) %>% map(find_pos_id_to_keep) %>% @@ -124,8 +125,9 @@ drop_cached_children <- function(pd) { #' Find the pos ids to keep #' #' To make a parse table shallow, we must know which ids to keep. -#' `split(cumsum(pd_parent_first$parent == 0))` above puts comments with negative -#' parents in the same block as proceeding expressions (but also with positive). +#' `split(cumsum(pd_parent_first$parent == 0))` above puts comments with +#' negative parents in the same block as proceeding expressions (but also with +#' positive). #' `find_pos_id_to_keep()` must hence always keep negative comments. We did not #' use `split(cumsum(pd_parent_first$parent < 1))` because then every top-level #' comment is an expression on its own and processing takes much longer for @@ -173,6 +175,7 @@ find_pos_id_to_keep <- function(pd) { #' option supports character vectors longer than one and the marker are not #' exactly matched, but using a regular expression, which means you can have #' multiple marker on one line, e.g. `# nolint start styler: off`. +# nolint end #' @name stylerignore #' @examples #' # as long as the order of the markers is correct, the lines are ignored. diff --git a/R/nested-to-tree.R b/R/nested-to-tree.R index 5b898b868..d43f48fb9 100644 --- a/R/nested-to-tree.R +++ b/R/nested-to-tree.R @@ -12,7 +12,8 @@ create_tree <- function(text, structure_only = FALSE) { create_tree_from_pd_with_default_style_attributes(structure_only) } -create_tree_from_pd_with_default_style_attributes <- function(pd, structure_only = FALSE) { +create_tree_from_pd_with_default_style_attributes <- function(pd, + structure_only = FALSE) { pd %>% create_node_from_nested_root(structure_only) %>% as.data.frame() @@ -35,8 +36,12 @@ create_tree_from_pd_with_default_style_attributes <- function(pd, structure_only #' { #' code <- "a <- function(x) { if(x > 1) { 1+1 } else {x} }" #' nested_pd <- styler:::compute_parse_data_nested(code) -#' initialized <- styler:::pre_visit(nested_pd, c(default_style_guide_attributes)) -#' styler:::create_node_from_nested_root(initialized, structure_only = FALSE) +#' initialized <- styler:::pre_visit( +#' nested_pd, c(default_style_guide_attributes) +#' ) +#' styler:::create_node_from_nested_root(initialized, +#' structure_only = FALSE +#' ) #' } #' ) #' } diff --git a/R/parse.R b/R/parse.R index f728f4583..3651ce2a7 100644 --- a/R/parse.R +++ b/R/parse.R @@ -27,8 +27,8 @@ parse_safely <- function(text, ...) { abort(paste0( "The code to style seems to use Windows style line endings (CRLF). ", "styler currently only supports Unix style line endings (LF). ", - "Please change the EOL character in your editor to Unix style and try again.", - "\nThe parsing error was:\n", tried_parsing$message + "Please change the EOL character in your editor to Unix style and try ", + "again.\nThe parsing error was:\n", tried_parsing$message )) } else { abort(tried_parsing$message) diff --git a/R/reindent.R b/R/reindent.R index be58c43c2..5e1080e35 100644 --- a/R/reindent.R +++ b/R/reindent.R @@ -1,42 +1,3 @@ -# @describeIn update_indention_ref Updates the reference pos_id for all -# tokens in `pd_nested` if `pd_nested` contains a function call. Tokens that -# start on the same line as the opening parenthesis, are not themselves -# function calls or expressions wrapped in curly brackets are re-indented, -# that is, they are indented up to the level at which the call ends in -# terms of col2. We need to take the last from the first child because calls -# like package::function() can have three elements. -# @examples -# \dontrun{ -# # not re-indented -# call(call( -# xyz -# )) -# # re-indented -# call(call(1, -# 2)) -# } -# @importFrom purrr map_lgl -# @importFrom rlang seq2 -# @keywords internal -# update_indention_ref_fun_call <- function(pd_nested) { -# current_is_call <- pd_nested$token_before[2] %in% c("SYMBOL_FUNCTION_CALL") -# non_comment <- which(pd_nested$token != "COMMENT") -# first_non_comment_after_call <- non_comment[non_comment > 2][1] -# if ((current_is_call) && -# pd_nested$lag_newlines[first_non_comment_after_call] == 0) { -# candidates <- seq2(3, nrow(pd_nested) - 1) -# -# child_is_call <- map_lgl(pd_nested$child, is_function_call) -# child_is_curly_expr <- map_lgl(pd_nested$child, is_curly_expr) -# child_is_on_same_line <- cumsum(pd_nested$lag_newlines) == 0 -# call_on_same_line <- child_is_call & child_is_on_same_line -# to_indent <- setdiff(candidates, which(call_on_same_line | child_is_curly_expr)) -# -# pd_nested$indention_ref_pos_id[to_indent] <- last(pd_nested$child[[1]]$pos_id) -# } -# pd_nested -# } - #' Apply reference indention to tokens #' #' Applies the reference indention created with functions @@ -46,7 +7,9 @@ #' @inheritParams apply_ref_indention_one #' @keywords internal apply_ref_indention <- function(flattened_pd) { - target_tokens <- which(flattened_pd$pos_id %in% flattened_pd$indention_ref_pos_id) + target_tokens <- which( + flattened_pd$pos_id %in% flattened_pd$indention_ref_pos_id + ) flattened_pd <- Reduce( apply_ref_indention_one, target_tokens, @@ -114,8 +77,8 @@ find_tokens_to_update <- function(flattened_pd, target_token) { #' expression pattern to be a certain amount of spaces. The rule #' is only active for the first tokens on a line. #' @param flattened_pd A flattened parse table. -#' @param pattern A character with regular expressions to match against the token -#' in `flattened_pd`. +#' @param pattern A character with regular expressions to match against the +#' token in `flattened_pd`. #' @param target_indention The desired level of indention of the tokens that #' match `pattern`. #' @param comments_only Boolean indicating whether only comments should be diff --git a/R/relevel.R b/R/relevel.R index 71cee0a10..92ed14965 100644 --- a/R/relevel.R +++ b/R/relevel.R @@ -27,7 +27,8 @@ flatten_operators <- function(pd_nested) { flatten_operators_one <- function(pd_nested) { pd_token_left <- c(special_token, "PIPE", math_token, "'$'") pd_token_right <- c( - special_token, "PIPE", "LEFT_ASSIGN", if (parser_version_get() > 1) "EQ_ASSIGN", + special_token, "PIPE", "LEFT_ASSIGN", + if (parser_version_get() > 1) "EQ_ASSIGN", "'+'", "'-'", "'~'" ) pd_nested %>% @@ -56,7 +57,9 @@ flatten_pd <- function(pd_nested, token, child_token = token, left = TRUE) { if (length(token_pos_candidates) == 0) { return(pd_nested) } - token_pos <- token_pos_candidates[ifelse(left, 1, length(token_pos_candidates))] + token_pos <- token_pos_candidates[ + ifelse(left, 1, length(token_pos_candidates)) + ] if (left) { pos <- previous_non_comment(pd_nested, token_pos) } else { diff --git a/R/roxygen-examples-find.R b/R/roxygen-examples-find.R index dfa021d92..1dddabc4e 100644 --- a/R/roxygen-examples-find.R +++ b/R/roxygen-examples-find.R @@ -53,7 +53,6 @@ match_stop_to_start <- function(start, stop_candidates) { #' @keywords internal find_dont_seqs <- function(bare) { dont_openings <- which(bare %in% dont_keywords()) - dont_type <- bare[dont_openings] dont_closings <- map_int(dont_openings + 1L, find_dont_closings, bare = bare) map2(dont_openings, dont_closings, seq2) } diff --git a/R/roxygen-examples-parse.R b/R/roxygen-examples-parse.R index 272c2f213..1812318b2 100644 --- a/R/roxygen-examples-parse.R +++ b/R/roxygen-examples-parse.R @@ -20,7 +20,8 @@ parse_roxygen <- function(roxygen) { had_warning <- FALSE parsed <- withCallingHandlers( { - parsed <- as.character(tools::parse_Rd(connection, fragment = TRUE), deparse = FALSE) + parsed <- tools::parse_Rd(connection, fragment = TRUE) %>% + as.character(deparse = FALSE) if (had_warning) { roxygen_remove_extra_brace(parsed) } else { @@ -93,15 +94,19 @@ roxygen_remove_extra_brace <- function(parsed) { # try if can be parsed (need remve dontrun) worth_trying_to_remove_brace <- rlang::with_handlers( { - parse(text = gsub("^\\\\[[:alpha:]]+", "", parsed)) # this will error informatively - FALSE # if parsing succeeds, we can stop tryint to remove brace and move on with parsed + # this will error informatively + parse(text = gsub("^\\\\[[:alpha:]]+", "", parsed)) + # if parsing succeeds, we can stop tryint to remove brace and move + # on with parsed + FALSE }, error = function(...) { # continue if braces are left, otherwise give up if (any(last(parsed) %in% c("}", "\n"))) { TRUE } else { - # this will error informatively. If not, outer loop will fail informatively + # this will error informatively. If not, outer loop will fail + # informatively parse(text = gsub("^\\\\[[:alpha:]]+", "", parsed_)) FALSE } @@ -109,7 +114,8 @@ roxygen_remove_extra_brace <- function(parsed) { ) } } else { - parse(text = gsub("^\\\\[[:alpha:]]*", "", parsed_)) # this will error informatively + # this will error informatively + parse(text = gsub("^\\\\[[:alpha:]]*", "", parsed_)) } parsed } @@ -124,11 +130,15 @@ roxygen_remove_extra_brace <- function(parsed) { #' `remove_roxygen_mask()` when there are no characters to escape. #' @keywords internal emulate_rd <- function(roxygen) { - example_type <- gsub("^#'(\\s|\t)*@examples(If)?(\\s|\t)*(.*)", "examples\\2", roxygen[1]) + example_type <- gsub( + "^#'(\\s|\t)*@examples(If)?(\\s|\t)*(.*)", "examples\\2", roxygen[1] + ) if (needs_rd_emulation(roxygen)) { roxygen <- c( "#' Example", - gsub("^#'(\\s|\t)*@examples(If)?(\\s|\t)*(.*)", "#' @examples \\4", roxygen), + gsub( + "^#'(\\s|\t)*@examples(If)?(\\s|\t)*(.*)", "#' @examples \\4", roxygen + ), "x <- 1" ) roxygen <- gsub("(^#)[^']", "#' #", roxygen) diff --git a/R/roxygen-examples.R b/R/roxygen-examples.R index b21ed4da9..16f077af5 100644 --- a/R/roxygen-examples.R +++ b/R/roxygen-examples.R @@ -22,7 +22,9 @@ style_roxygen_code_example <- function(example, transformers, base_indention) { #' @param example_one A character vector, one element per line, that contains in #' total at most one example tag. #' @keywords internal -style_roxygen_code_example_one <- function(example_one, transformers, base_indention) { +style_roxygen_code_example_one <- function(example_one, + transformers, + base_indention) { bare <- parse_roxygen(example_one) one_dont <- split(bare$text, factor(cumsum(bare$text %in% dont_keywords()))) unmasked <- map(one_dont, style_roxygen_code_example_segment, @@ -52,9 +54,9 @@ style_roxygen_code_example_one <- function(example_one, transformers, base_inden #' contains at most one `\\dontrun{...}` or friends. #' We drop all newline characters first because otherwise the code segment #' passed to this function was previously parsed with [parse_roxygen()] and -#' line-breaks in and after the `\\dontrun{...}` are expressed with `"\n"`, which -#' contradicts to the definition used elsewhere in this package, where every -#' element in a vector corresponds to a line. These line-breaks don't get +#' line-breaks in and after the `\\dontrun{...}` are expressed with `"\n"`, +#' which contradicts to the definition used elsewhere in this package, where +#' every element in a vector corresponds to a line. These line-breaks don't get #' eliminated because they move to the front of a `code_segment` and #' `style_text("\n1")` gives `"\n1"`, i.e. trailing newlines are not #' eliminated. diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 40d3c42a4..ac2214f59 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -72,25 +72,35 @@ set_line_break_before_curly_opening <- function(pd) { no_line_break_before_curly_idx <- pd$token[line_break_to_set_idx] %in% "EQ_SUB" linebreak_before_curly <- ifelse(is_function_call(pd), - # if in function call and has pipe, it is not recognized as function call and - # goes to else case + # if in function call and has pipe, it is not recognized as function call + # and goes to else case any(pd$lag_newlines[seq2(1, line_break_to_set_idx[1])] > 0), # if not a function call, only break line if it is a pipe followed by {} pd$token[line_break_to_set_idx] %in% c("SPECIAL-PIPE", "PIPE") ) # no line break before last brace expression and named brace expression to should_be_on_same_line <- is_not_curly_curly & - ((is_last_expr & !linebreak_before_curly) | no_line_break_before_curly_idx) + ( + (is_last_expr & !linebreak_before_curly) | + no_line_break_before_curly_idx + ) is_not_curly_curly_idx <- line_break_to_set_idx[should_be_on_same_line] pd$lag_newlines[1 + is_not_curly_curly_idx] <- 0L # other cases: line breaks should_not_be_on_same_line <- is_not_curly_curly & - ((!is_last_expr | linebreak_before_curly) & !no_line_break_before_curly_idx) - should_not_be_on_same_line_idx <- line_break_to_set_idx[should_not_be_on_same_line] + ( + (!is_last_expr | linebreak_before_curly) & + !no_line_break_before_curly_idx + ) + should_not_be_on_same_line_idx <- line_break_to_set_idx[ + should_not_be_on_same_line + ] if (is_function_dec(pd)) { - should_not_be_on_same_line_idx <- setdiff(1 + should_not_be_on_same_line_idx, nrow(pd)) + should_not_be_on_same_line_idx <- setdiff( + 1 + should_not_be_on_same_line_idx, nrow(pd) + ) } else { should_not_be_on_same_line_idx <- 1 + should_not_be_on_same_line_idx } @@ -104,8 +114,9 @@ set_line_break_before_curly_opening <- function(pd) { next_non_comment, pd = pd ) - non_comment_after_expr <- - non_comment_after_comma[non_comment_after_comma > should_not_be_on_same_line_idx[1]] + non_comment_after_expr <- non_comment_after_comma[ + non_comment_after_comma > should_not_be_on_same_line_idx[1] + ] pd$lag_newlines[non_comment_after_comma] <- 1L } } @@ -185,8 +196,8 @@ style_line_break_around_curly <- function(strict, pd) { #' curly-curly affects styling of line break and spaces, namely: #' #' * No line break after first or second `\{`, before third and fourth `\{`. -#' * No space after first and third `\{`, one space after second and before third -#' `\}`. +#' * No space after first and third `\{`, one space after second and before +#' third `\}`. #' * No line breaks within curly-curly, e.g. `\{\{ x \}\}` can only contain line #' breaks after the last brace or before the first brace. But these are not #' dependent on curly-curly specifically. @@ -219,7 +230,11 @@ remove_line_break_before_round_closing_after_curly <- function(pd) { remove_line_breaks_in_fun_dec <- function(pd) { if (is_function_dec(pd)) { - round_after <- (pd$token == "')'" | pd$token_before == "'('") & pd$token_before != "COMMENT" + round_after <- ( + pd$token == "')'" | pd$token_before == "'('" + ) & + pd$token_before != "COMMENT" + pd$lag_newlines[pd$lag_newlines > 1L] <- 1L pd$lag_newlines[round_after] <- 0L } @@ -351,7 +366,9 @@ remove_line_break_in_fun_call <- function(pd, strict) { if (is_function_call(pd)) { # no blank lines within function calls if (strict) { - pd$lag_newlines[lag(pd$token == "','") & pd$lag_newlines > 1 & pd$token != "COMMENT"] <- 1L + pd$lag_newlines[ + lag(pd$token == "','") & pd$lag_newlines > 1 & pd$token != "COMMENT" + ] <- 1L } if (nrow(pd) == 3) { pd$lag_newlines[3] <- 0L diff --git a/R/style-guides.R b/R/style-guides.R index 8b430fb14..4de3211f1 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -89,7 +89,9 @@ tidyverse_style <- function(scope = "tokens", space_manipulators <- if ("spaces" %in% scope) { list( remove_space_before_closing_paren = remove_space_before_closing_paren, - remove_space_before_opening_paren = if (strict) remove_space_before_opening_paren, + remove_space_before_opening_paren = if (strict) { + remove_space_before_opening_paren + }, add_space_after_for_if_while = add_space_after_for_if_while, remove_space_before_comma = remove_space_before_comma, style_space_around_math_token = partial( @@ -153,13 +155,19 @@ tidyverse_style <- function(scope = "tokens", partial( set_line_break_after_opening_if_call_is_multi_line, except_token_after = "COMMENT", - except_text_before = c("ifelse", "if_else"), # don't modify line break here + # don't modify line break here + except_text_before = c("ifelse", "if_else"), force_text_before = c("switch") # force line break after first token ) }, - remove_line_break_in_fun_call = purrr::partial(remove_line_break_in_fun_call, strict = strict), + remove_line_break_in_fun_call = purrr::partial( + remove_line_break_in_fun_call, + strict = strict + ), add_line_break_after_pipe = if (strict) add_line_break_after_pipe, - set_linebreak_after_ggplot2_plus = if (strict) set_linebreak_after_ggplot2_plus + set_linebreak_after_ggplot2_plus = if (strict) { + set_linebreak_after_ggplot2_plus + } ) } @@ -224,7 +232,9 @@ tidyverse_style <- function(scope = "tokens", # contain EQ_ASSIGN, and the transformer is falsely removed. # compute_parse_data_nested / text_to_flat_pd ('a = 4') force_assignment_op = "EQ_ASSIGN", - wrap_if_else_while_for_fun_multi_line_in_curly = c("IF", "WHILE", "FOR", "FUNCTION") + wrap_if_else_while_for_fun_multi_line_in_curly = c( + "IF", "WHILE", "FOR", "FUNCTION" + ) ) ) diff --git a/R/token-create.R b/R/token-create.R index 5b4eec99c..a32afa35f 100644 --- a/R/token-create.R +++ b/R/token-create.R @@ -81,7 +81,9 @@ create_tokens <- function(tokens, create_pos_ids <- function(pd, pos, by = 0.1, after = FALSE, n = 1) { direction <- ifelse(after, 1L, -1L) first <- find_start_pos_id(pd, pos, by, direction, after) - new_ids <- seq(first, to = first + direction * (n - 1) * by, by = by * direction) + new_ids <- seq(first, + to = first + direction * (n - 1) * by, by = by * direction + ) validate_new_pos_ids(new_ids, after) new_ids } @@ -96,7 +98,12 @@ create_pos_ids <- function(pd, pos, by = 0.1, after = FALSE, n = 1) { #' nests. #' @inheritParams create_pos_ids #' @keywords internal -find_start_pos_id <- function(pd, pos, by, direction, after, candidates = NULL) { +find_start_pos_id <- function(pd, + pos, + by, + direction, + after, + candidates = NULL) { candidates <- append(candidates, pd$pos_id[pos]) if (is.null(pd$child[[pos]])) { ifelse(after, max(candidates), min(candidates)) + by * direction diff --git a/R/transform-block.R b/R/transform-block.R index 2b31ac42a..a188c4a4e 100644 --- a/R/transform-block.R +++ b/R/transform-block.R @@ -18,7 +18,9 @@ #' ' #' style_text(text_in, base_indention = 3) #' # not equal to the naive approach -#' styler:::construct_vertical(paste0(styler:::add_spaces(3), style_text(text_in), sep = "")) +#' styler:::construct_vertical( +#' paste0(styler:::add_spaces(3), style_text(text_in), sep = "") +#' ) #' @keywords internal parse_transform_serialize_r_block <- function(pd_nested, start_line, diff --git a/R/transform-code.R b/R/transform-code.R index de7b8a44b..f17fcd821 100644 --- a/R/transform-code.R +++ b/R/transform-code.R @@ -1,8 +1,8 @@ #' Transform code from R, Rmd or Rnw files #' #' A wrapper which initiates the styling of -#' either R, Rmd or Rnw files by passing the relevant transformer function for each -#' case. +#' either R, Rmd or Rnw files by passing the relevant transformer function for +#' each case. #' #' @inheritParams transform_utf8 #' @param ... Further arguments passed to [transform_utf8()]. @@ -29,8 +29,8 @@ transform_code <- function(path, fun, ..., dry) { #' Transform mixed contents #' #' Applies the supplied transformer function to code chunks identified within -#' an Rmd or Rnw file and recombines the resulting (styled) code chunks with the text -#' chunks. +#' an Rmd or Rnw file and recombines the resulting (styled) code chunks with the +#' text chunks. #' #' @param transformer_fun A styler transformer function. #' @inheritParams separate_chunks @@ -93,14 +93,19 @@ separate_chunks <- function(lines, filetype) { #' @param engine_pattern A regular expression that must match the engine name. #' @importFrom rlang abort #' @keywords internal -identify_raw_chunks <- function(lines, filetype, engine_pattern = get_engine_pattern()) { +identify_raw_chunks <- function(lines, + filetype, + engine_pattern = get_engine_pattern()) { pattern <- get_knitr_pattern(filetype) if (is.null(pattern$chunk.begin) || is.null(pattern$chunk.end)) { abort("Unrecognized chunk pattern!") } if (filetype == "Rmd") { - starts <- grep("^[\t >]*```+\\s*\\{([Rr]( *[ ,].*)?)\\}\\s*$", lines, perl = TRUE) + starts <- grep( + "^[\t >]*```+\\s*\\{([Rr]( *[ ,].*)?)\\}\\s*$", lines, + perl = TRUE + ) ends <- grep("^[\t >]*```+\\s*$", lines, perl = TRUE) ends <- purrr::imap_int(starts, ~ ends[which(ends > .x)[1]]) %>% stats::na.omit() diff --git a/R/transform-files.R b/R/transform-files.R index f4983cfae..cf527a16a 100644 --- a/R/transform-files.R +++ b/R/transform-files.R @@ -11,8 +11,14 @@ #' styling whether or not it was actually changed (or would be changed when #' `dry` is not "off"). #' @keywords internal -transform_files <- function(files, transformers, include_roxygen_examples, base_indention, dry) { - transformer <- make_transformer(transformers, include_roxygen_examples, base_indention) +transform_files <- function(files, + transformers, + include_roxygen_examples, + base_indention, + dry) { + transformer <- make_transformer( + transformers, include_roxygen_examples, base_indention + ) max_char <- min(max(nchar(files), 0), getOption("width")) len_files <- length(files) if (len_files > 0L && !getOption("styler.quiet", FALSE)) { @@ -155,7 +161,9 @@ make_transformer <- function(transformers, #' [parse_transform_serialize_r()]. #' @importFrom purrr map_at flatten_chr #' @keywords internal -parse_transform_serialize_roxygen <- function(text, transformers, base_indention) { +parse_transform_serialize_roxygen <- function(text, + transformers, + base_indention) { roxygen_seqs <- identify_start_to_stop_of_roxygen_examples_from_text(text) if (length(roxygen_seqs) < 1L) { return(text) diff --git a/R/ui-styling.R b/R/ui-styling.R index 50c69875c..7c26d2265 100644 --- a/R/ui-styling.R +++ b/R/ui-styling.R @@ -227,12 +227,12 @@ style_text <- function(text, #' Prettify arbitrary R code #' #' Performs various substitutions in all `.R`, `.Rmd`, `.Rmarkdown`, `qmd` -#' and/or `.Rnw` files -#' in a directory (by default only `.R` files are styled - see `filetype` argument). +#' and/or `.Rnw` files in a directory (by default only `.R` files are styled - +#' see `filetype` argument). #' Carefully examine the results after running this function! #' @param path Path to a directory with files to transform. -#' @param recursive A logical value indicating whether or not files in subdirectories -#' of `path` should be styled as well. +#' @param recursive A logical value indicating whether or not files in +#' sub directories of `path` should be styled as well. #' @param exclude_dirs Character vector with directories to exclude #' (recursively). ##' @inheritParams style_pkg diff --git a/R/unindent.R b/R/unindent.R index 69bd29330..fe0144bfb 100644 --- a/R/unindent.R +++ b/R/unindent.R @@ -15,7 +15,9 @@ set_unindention_child <- function(pd, token = "')'", unindent_by) { return(pd) } - first_on_last_line <- last(c(1, which(pd$lag_newlines > 0 | pd$multi_line > 0))) + first_on_last_line <- last( + c(1, which(pd$lag_newlines > 0 | pd$multi_line > 0)) + ) on_same_line <- seq2(first_on_last_line, closing - 1) cand_ind <- setdiff(on_same_line, which(pd$terminal)) diff --git a/R/utils-cache.R b/R/utils-cache.R index 1eaecb0bd..1988be014 100644 --- a/R/utils-cache.R +++ b/R/utils-cache.R @@ -158,8 +158,9 @@ cache_by_expression <- function(text, } # TODO base_indention should be set to 0 on write and on read for expressions # (only) to make it possible to use the cache for expressions with different - # indention. when not the whole input text is cached, we go trough all expressions and - # check if they are cached, if yes, we take the input (from which the indention + # indention. when not the whole input text is cached, we go trough all + # expressions and check if they are cached, if yes, we take the input (from + # which the indention # was removed via parse, same as it is in cache_by_expression) and add the # base indention. expressions[expressions$parent == 0 & expressions$token != "COMMENT" & !expressions$stylerignore, "text"] %>% diff --git a/R/utils-files.R b/R/utils-files.R index e1890cd60..1e5a16d70 100644 --- a/R/utils-files.R +++ b/R/utils-files.R @@ -29,7 +29,11 @@ is_unsaved_file <- function(path) { #' styler:::map_filetype_to_pattern(c(".rMd", "R")) #' @keywords internal map_filetype_to_pattern <- function(filetype) { - paste0("(", paste(set_and_assert_arg_filetype(filetype), collapse = "|"), ")$") + paste0( + "(", + paste(set_and_assert_arg_filetype(filetype), collapse = "|"), + ")$" + ) } #' `dir()`, but without dot-prefix and different defaults diff --git a/R/utils-navigate-nest.R b/R/utils-navigate-nest.R index 00ab0b186..b3c193ec9 100644 --- a/R/utils-navigate-nest.R +++ b/R/utils-navigate-nest.R @@ -64,7 +64,10 @@ next_terminal <- function(pd, if (pd$terminal[1]) { pd[1, c("position", vars)] } else { - current <- next_terminal(pd$child[[1]], stack = stack, vars = vars, tokens_exclude = tokens_exclude) + current <- next_terminal( + pd$child[[1]], + stack = stack, vars = vars, tokens_exclude = tokens_exclude + ) if (stack) { bind_rows(pd[1, c("position", vars)], current) } else { diff --git a/R/utils.R b/R/utils.R index 850ff65ec..187419d8d 100644 --- a/R/utils.R +++ b/R/utils.R @@ -87,6 +87,7 @@ calls_sys <- function(sys_call, ...) { } else { error <- system(sys_call, ...) } + error } #' Get the value of an option diff --git a/R/visit.R b/R/visit.R index 7f9383598..a17742fe2 100644 --- a/R/visit.R +++ b/R/visit.R @@ -128,7 +128,8 @@ context_towards_terminals <- function(pd_nested, #' @keywords internal extract_terminals <- function(pd_nested) { bind_rows( - ifelse(pd_nested$terminal | pd_nested$is_cached, split(pd_nested, seq_len(nrow(pd_nested))), + ifelse(pd_nested$terminal | pd_nested$is_cached, + split(pd_nested, seq_len(nrow(pd_nested))), pd_nested$child ) ) diff --git a/man/create_node_from_nested_root.Rd b/man/create_node_from_nested_root.Rd index fc4c86289..14af8366e 100644 --- a/man/create_node_from_nested_root.Rd +++ b/man/create_node_from_nested_root.Rd @@ -27,8 +27,12 @@ if (rlang::is_installed("data.tree")) { { code <- "a <- function(x) { if(x > 1) { 1+1 } else {x} }" nested_pd <- styler:::compute_parse_data_nested(code) - initialized <- styler:::pre_visit(nested_pd, c(default_style_guide_attributes)) - styler:::create_node_from_nested_root(initialized, structure_only = FALSE) + initialized <- styler:::pre_visit( + nested_pd, c(default_style_guide_attributes) + ) + styler:::create_node_from_nested_root(initialized, + structure_only = FALSE + ) } ) } diff --git a/man/find_pos_id_to_keep.Rd b/man/find_pos_id_to_keep.Rd index c49b4c0aa..4ad0b6305 100644 --- a/man/find_pos_id_to_keep.Rd +++ b/man/find_pos_id_to_keep.Rd @@ -12,8 +12,9 @@ top level expression, potentially cached.} } \description{ To make a parse table shallow, we must know which ids to keep. -\code{split(cumsum(pd_parent_first$parent == 0))} above puts comments with negative -parents in the same block as proceeding expressions (but also with positive). +\code{split(cumsum(pd_parent_first$parent == 0))} above puts comments with +negative parents in the same block as proceeding expressions (but also with +positive). \code{find_pos_id_to_keep()} must hence always keep negative comments. We did not use \code{split(cumsum(pd_parent_first$parent < 1))} because then every top-level comment is an expression on its own and processing takes much longer for diff --git a/man/parse_transform_serialize_r_block.Rd b/man/parse_transform_serialize_r_block.Rd index 5dc55a15a..e19f62bea 100644 --- a/man/parse_transform_serialize_r_block.Rd +++ b/man/parse_transform_serialize_r_block.Rd @@ -36,6 +36,8 @@ NULL ' style_text(text_in, base_indention = 3) # not equal to the naive approach -styler:::construct_vertical(paste0(styler:::add_spaces(3), style_text(text_in), sep = "")) +styler:::construct_vertical( + paste0(styler:::add_spaces(3), style_text(text_in), sep = "") +) } \keyword{internal} diff --git a/man/parser_version_set.Rd b/man/parser_version_set.Rd index fea089adb..d740077a1 100644 --- a/man/parser_version_set.Rd +++ b/man/parser_version_set.Rd @@ -24,11 +24,11 @@ unexpected behavior of the parser that styler was initially designed to work around. Examples are \href{https://github.com/r-lib/styler/issues/187}{#187}, \href{https://github.com/r-lib/styler/issues/216}{#216}, \href{https://github.com/r-lib/styler/issues/100}{#100} and others. With -\href{https://github.com/r-lib/styler/issues/419}{#419}, the structure of the parse -data changes and we need to dispatch for older versions. As it is inconvenient -to pass a parser version down in the call stack in various places, the -environment \code{env_current} is used to store the current version \emph{globally} -but internally. +\href{https://github.com/r-lib/styler/issues/419}{#419}, the structure of the +parse data changes and we need to dispatch for older versions. As it is +inconvenient to pass a parser version down in the call stack in various +places, the environment \code{env_current} is used to store the current version +\emph{globally} but internally. } \details{ We version the parser as follows: diff --git a/man/set_line_break_around_curly_curly.Rd b/man/set_line_break_around_curly_curly.Rd index ac00c167f..4b100dda4 100644 --- a/man/set_line_break_around_curly_curly.Rd +++ b/man/set_line_break_around_curly_curly.Rd @@ -35,8 +35,8 @@ curly-curly affects styling of line break and spaces, namely: \details{ \itemize{ \item No line break after first or second \verb{\\\{}, before third and fourth \verb{\\\{}. -\item No space after first and third \verb{\\\{}, one space after second and before third -\verb{\\\}}. +\item No space after first and third \verb{\\\{}, one space after second and before +third \verb{\\\}}. \item No line breaks within curly-curly, e.g. \verb{\\\{\\\{ x \\\}\\\}} can only contain line breaks after the last brace or before the first brace. But these are not dependent on curly-curly specifically. diff --git a/man/set_regex_indention.Rd b/man/set_regex_indention.Rd index 1d5226a19..d856207d5 100644 --- a/man/set_regex_indention.Rd +++ b/man/set_regex_indention.Rd @@ -14,8 +14,8 @@ set_regex_indention( \arguments{ \item{flattened_pd}{A flattened parse table.} -\item{pattern}{A character with regular expressions to match against the token -in \code{flattened_pd}.} +\item{pattern}{A character with regular expressions to match against the +token in \code{flattened_pd}.} \item{target_indention}{The desired level of indention of the tokens that match \code{pattern}.} diff --git a/man/style_dir.Rd b/man/style_dir.Rd index 9d94f5b11..aeea28162 100644 --- a/man/style_dir.Rd +++ b/man/style_dir.Rd @@ -37,8 +37,8 @@ be styled. Case is ignored, and the \code{.} is optional, e.g. \code{c(".R", ".Rmd")}, or \code{c("r", "rmd")}. Supported values (after standardization) are: "r", "rprofile", "rmd", "rmarkdown", "rnw". Rmarkdown is treated as Rmd.} -\item{recursive}{A logical value indicating whether or not files in subdirectories -of \code{path} should be styled as well.} +\item{recursive}{A logical value indicating whether or not files in +sub directories of \code{path} should be styled as well.} \item{exclude_files}{Character vector with paths to files that should be excluded from styling.} @@ -62,8 +62,8 @@ styling are not identical.} } \description{ Performs various substitutions in all \code{.R}, \code{.Rmd}, \code{.Rmarkdown}, \code{qmd} -and/or \code{.Rnw} files -in a directory (by default only \code{.R} files are styled - see \code{filetype} argument). +and/or \code{.Rnw} files in a directory (by default only \code{.R} files are styled - +see \code{filetype} argument). Carefully examine the results after running this function! } \section{Value}{ diff --git a/man/style_roxygen_code_example_segment.Rd b/man/style_roxygen_code_example_segment.Rd index 2c55c5dcd..9112ba51f 100644 --- a/man/style_roxygen_code_example_segment.Rd +++ b/man/style_roxygen_code_example_segment.Rd @@ -22,9 +22,9 @@ A roxygen code example segment corresponds to roxygen example code that contains at most one \verb{\\\dontrun{...}} or friends. We drop all newline characters first because otherwise the code segment passed to this function was previously parsed with \code{\link[=parse_roxygen]{parse_roxygen()}} and -line-breaks in and after the \verb{\\\dontrun{...}} are expressed with \code{"\\n"}, which -contradicts to the definition used elsewhere in this package, where every -element in a vector corresponds to a line. These line-breaks don't get +line-breaks in and after the \verb{\\\dontrun{...}} are expressed with \code{"\\n"}, +which contradicts to the definition used elsewhere in this package, where +every element in a vector corresponds to a line. These line-breaks don't get eliminated because they move to the front of a \code{code_segment} and \code{style_text("\\n1")} gives \code{"\\n1"}, i.e. trailing newlines are not eliminated. diff --git a/man/styler_addins.Rd b/man/styler_addins.Rd index 24daeb37f..219dd4e8a 100644 --- a/man/styler_addins.Rd +++ b/man/styler_addins.Rd @@ -51,8 +51,9 @@ the current status of this. # save after styling when using the Addin options(styler.save_after_styling = TRUE) # only style with scope = "spaces" when using the Addin +val <- "styler::tidyverse_style(scope = 'spaces')" options( - styler.addins_style_transformer = "styler::tidyverse_style(scope = 'spaces')" + styler.addins_style_transformer = val ) } } diff --git a/man/transform_code.Rd b/man/transform_code.Rd index 857bb636f..cd3258734 100644 --- a/man/transform_code.Rd +++ b/man/transform_code.Rd @@ -21,7 +21,7 @@ styling are not identical.} } \description{ A wrapper which initiates the styling of -either R, Rmd or Rnw files by passing the relevant transformer function for each -case. +either R, Rmd or Rnw files by passing the relevant transformer function for +each case. } \keyword{internal} diff --git a/man/transform_mixed.Rd b/man/transform_mixed.Rd index 6f286ef9c..9fae81d99 100644 --- a/man/transform_mixed.Rd +++ b/man/transform_mixed.Rd @@ -15,7 +15,7 @@ transform_mixed(lines, transformer_fun, filetype) } \description{ Applies the supplied transformer function to code chunks identified within -an Rmd or Rnw file and recombines the resulting (styled) code chunks with the text -chunks. +an Rmd or Rnw file and recombines the resulting (styled) code chunks with the +text chunks. } \keyword{internal} diff --git a/man/update_indention.Rd b/man/update_indention.Rd index 9834753ef..377568c39 100644 --- a/man/update_indention.Rd +++ b/man/update_indention.Rd @@ -40,8 +40,8 @@ Update indention information of parse data } \section{Functions}{ \itemize{ -\item \code{indent_without_paren_for_while_fun}: Is used to indent for and statements and function -definitions without parenthesis. +\item \code{indent_without_paren_for_while_fun}: Is used to indent for and statements and +function definitions without parenthesis. \item \code{indent_without_paren_if_else}: Is used to indent if and if-else statements. diff --git a/man/update_newlines.Rd b/man/update_newlines.Rd index 353c41caa..7efa91981 100644 --- a/man/update_newlines.Rd +++ b/man/update_newlines.Rd @@ -10,7 +10,8 @@ update_newlines(pd) \item{pd}{A parse table.} } \value{ -A parse table with synchronized \code{lag_newlines} and \code{newlines} columns. +A parse table with synchronized \code{lag_newlines} and \code{newlines} +columns. } \description{ As we work only with the \code{lag_newlines} attribute for setting the line