diff --git a/.Rbuildignore b/.Rbuildignore index e45fa7c85..8bffc965b 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -5,10 +5,8 @@ ^API$ ^README\.Rmd$ ^README-.*\.png$ -^.travis.yml ^appveyor\.yml$ ^tic\.R$ -^\.travis\.yml$ ^docs$ ^_pkgdown\.yml$ CONTRIBUTING.md @@ -20,5 +18,5 @@ revdep ^\.pre-commit-config\.yaml$ ^brew\-log$ ^\.github/$ -^touchstone/$ -^.github/$ +^touchstone$ +^\.github$ diff --git a/API b/API index f95f8c1bf..80b09fbe1 100644 --- a/API +++ b/API @@ -6,10 +6,11 @@ cache_activate(cache_name = NULL, verbose = TRUE) cache_clear(cache_name = NULL, ask = TRUE) cache_deactivate(verbose = TRUE) cache_info(cache_name = NULL, format = "both") -create_style_guide(initialize = default_style_guide_attributes, line_break = NULL, space = NULL, token = NULL, indention = NULL, use_raw_indention = FALSE, reindention = tidyverse_reindention(), style_guide_name = NULL, style_guide_version = NULL, more_specs_style_guide = NULL) +create_style_guide(initialize = default_style_guide_attributes, line_break = NULL, space = NULL, token = NULL, indention = NULL, use_raw_indention = FALSE, reindention = tidyverse_reindention(), style_guide_name = NULL, style_guide_version = NULL, more_specs_style_guide = NULL, transformers_drop = specify_transformers_drop()) default_style_guide_attributes(pd_flat) specify_math_token_spacing(zero = "'^'", one = c("'+'", "'-'", "'*'", "'/'")) specify_reindention(regex_pattern = NULL, indention = 0, comments_only = TRUE) +specify_transformers_drop(spaces = NULL, indention = NULL, line_breaks = NULL, tokens = NULL) style_dir(path = ".", ..., style = tidyverse_style, transformers = style(...), filetype = c("R", "Rprofile"), recursive = TRUE, exclude_files = NULL, exclude_dirs = c("packrat", "renv"), include_roxygen_examples = TRUE, base_indention = 0, dry = "off") style_file(path, ..., style = tidyverse_style, transformers = style(...), include_roxygen_examples = TRUE, base_indention = 0, dry = "off") style_pkg(pkg = ".", ..., style = tidyverse_style, transformers = style(...), filetype = c("R", "Rprofile"), exclude_files = "R/RcppExports.R", exclude_dirs = c("packrat", "renv"), include_roxygen_examples = TRUE, base_indention = 0, dry = "off") diff --git a/NAMESPACE b/NAMESPACE index 67f3fcd43..7ab16f529 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -9,6 +9,7 @@ export(create_style_guide) export(default_style_guide_attributes) export(specify_math_token_spacing) export(specify_reindention) +export(specify_transformers_drop) export(style_dir) export(style_file) export(style_pkg) diff --git a/NEWS.md b/NEWS.md index 08eb85409..125839a46 100644 --- a/NEWS.md +++ b/NEWS.md @@ -21,6 +21,11 @@ style tokens, you had to always also style spaces, indention, line breaks as well (#705, #707). +- New argument `transformers_drop` in `create_style_guide()` to be populated with + new helper function `specify_transformers_drop()` for specifying conditions + under which transformers are not going to be used and can therefore be + omitted without effecting the result of styling (#711). + ## Major changes @@ -31,9 +36,10 @@ or focus loss, so this feature becomes less relevant. (#631). - blank lines in function calls and headers are now removed, for the former only when there are no comments before or after the blank line (#629, #630, #635). -- speed improvements: (~10%) when cache is activated because transformers are not - captured as character anymore (#679), ~ 3% in low-level optimization (#691). - Require magrittr 2.0 gives about 7% speed improvement (#681). +- speed improvements: ~10% when cache is activated because transformers are not + captured as character anymore (#679), ~3% in low-level optimization (#691). + 7% by requiring magrittr 2.0 (#681), ~8% by dropping unused transformers + (#711) . - `#<<` is now recognized as the xaringan marker and no space is added after`#` (#700). diff --git a/R/rules-spaces.R b/R/rules-spaces.R index 7c6b7ed12..72f53da72 100644 --- a/R/rules-spaces.R +++ b/R/rules-spaces.R @@ -185,20 +185,6 @@ set_space_in_curly_curly <- function(pd) { pd } -add_space_before_brace <- function(pd_flat) { - # TODO remove this, it has no effect since { can only appear in the first - # position of the nest and taking lead(op_after, default = FALSE) will always - # yield a vector of FALSE only. - op_after <- pd_flat$token %in% "'{'" - if (!any(op_after)) { - return(pd_flat) - } - op_before <- lead(op_after, default = FALSE) - idx_before <- op_before & (pd_flat$newlines == 0L) & pd_flat$token != "'('" - pd_flat$spaces[idx_before] <- pmax(pd_flat$spaces[idx_before], 1L) - pd_flat -} - add_space_after_comma <- function(pd_flat) { comma_after <- (pd_flat$token == "','") & (pd_flat$newlines == 0L) pd_flat$spaces[comma_after] <- pmax(pd_flat$spaces[comma_after], 1L) diff --git a/R/style-guides.R b/R/style-guides.R index aeb3140d7..5fae0f40c 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -74,25 +74,23 @@ tidyverse_style <- function(scope = "tokens", indention_manipulators <- if ("indention" %in% scope) { - lst( + list( indent_braces = partial(indent_braces, indent_by = indent_by), - unindent_fun_dec, + unindent_fun_dec = unindent_fun_dec, indent_op = partial(indent_op, indent_by = indent_by), indent_eq_sub = partial(indent_eq_sub, indent_by = indent_by), indent_without_paren = partial(indent_without_paren, indent_by = indent_by ), - update_indention_ref_fun_dec = - if ("indention" %in% scope) update_indention_ref_fun_dec + update_indention_ref_fun_dec = update_indention_ref_fun_dec ) } space_manipulators <- if ("spaces" %in% scope) { - lst( - remove_space_before_closing_paren, + list( + remove_space_before_closing_paren = remove_space_before_closing_paren, remove_space_before_opening_paren = if (strict) remove_space_before_opening_paren, - add_space_after_for_if_while, - add_space_before_brace, - remove_space_before_comma, + 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( style_space_around_math_token, strict, math_token_spacing$zero, @@ -105,34 +103,34 @@ tidyverse_style <- function(scope = "tokens", spacing_around_op = purrr::partial(set_space_around_op, strict = strict ), - remove_space_after_opening_paren, - remove_space_after_excl, - set_space_after_bang_bang, - remove_space_before_dollar, - remove_space_after_fun_dec, - remove_space_around_colons, + remove_space_after_opening_paren = remove_space_after_opening_paren, + remove_space_after_excl = remove_space_after_excl, + set_space_after_bang_bang = set_space_after_bang_bang, + remove_space_before_dollar = remove_space_before_dollar, + remove_space_after_fun_dec = remove_space_after_fun_dec, + remove_space_around_colons = remove_space_around_colons, start_comments_with_space = partial(start_comments_with_space, force_one = start_comments_with_one_space ), - remove_space_after_unary_pm_nested, + remove_space_after_unary_pm_nested = remove_space_after_unary_pm_nested, spacing_before_comments = if (strict) { set_space_before_comments } else { add_space_before_comments }, - set_space_between_levels, - set_space_between_eq_sub_and_comma, - set_space_in_curly_curly + 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 ) } use_raw_indention <- !("indention" %in% scope) line_break_manipulators <- if ("line_breaks" %in% scope) { - lst( - set_line_break_around_comma_and_or, - set_line_break_after_assignment, - set_line_break_before_curly_opening, + list( + 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, remove_line_break_before_round_closing_after_curly = if (strict) remove_line_break_before_round_closing_after_curly, remove_line_breaks_in_fun_dec = @@ -143,7 +141,7 @@ tidyverse_style <- function(scope = "tokens", ), # must be after style_line_break_around_curly as it remove line # breaks again for {{. - set_line_break_around_curly_curly, + set_line_break_around_curly_curly = set_line_break_around_curly_curly, set_line_break_after_opening_if_call_is_multi_line = if (strict) { partial( set_line_break_after_opening_if_call_is_multi_line, @@ -157,24 +155,77 @@ tidyverse_style <- function(scope = "tokens", except_token_before = "COMMENT" ) }, - 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 ) } token_manipulators <- if ("tokens" %in% scope) { - lst( - fix_quotes, - force_assignment_op, - resolve_semicolon, - add_brackets_in_pipe, - remove_terminal_token_before_and_after, + list( + fix_quotes = fix_quotes, + force_assignment_op = force_assignment_op, + resolve_semicolon = resolve_semicolon, + add_brackets_in_pipe = add_brackets_in_pipe, + remove_terminal_token_before_and_after = remove_terminal_token_before_and_after, wrap_if_else_while_for_fun_multi_line_in_curly = if (strict) wrap_if_else_while_for_fun_multi_line_in_curly ) } + transformers_drop <- specify_transformers_drop( + spaces = list( + # remove_space_before_closing_paren = c("')'", "']'"), + # remove_space_before_opening_paren = c("'('", "'['", "LBB"), + add_space_after_for_if_while = c("IF", "WHILE", "FOR"), + # remove_space_before_comma = "','", + set_space_between_eq_sub_and_comma = "EQ_SUB", + style_space_around_math_token = c( + math_token_spacing$zero, + math_token_spacing$one + ), + style_space_around_tilde = "'~'", + # remove_space_after_opening_paren = c("'('", "'['", "LBB"), + remove_space_after_excl = "'!'", + set_space_after_bang_bang = "'!'", + remove_space_before_dollar = "'$'", + remove_space_after_fun_dec = "FUNCTION", + remove_space_around_colons = c("':'", "NS_GET_INT", "NS_GET"), + start_comments_with_space = "COMMENT", + remove_space_after_unary_pm_nested = c("'+'", "'-'"), + spacing_before_comments = "COMMENT", + set_space_in_curly_curly = c("'{'", "'}'") + ), + indention = list( + # indent_braces = c("'('", "'['", "'{'", "')'", "']'", "'}'"), + unindent_fun_dec = "FUNCTION", + indent_eq_sub = c("EQ_SUB", "EQ_FORMALS"), # TODO rename + update_indention_ref_fun_dec = "FUNCTION" + ), + line_breaks = list( + set_line_break_before_curly_opening = "'{'", + remove_line_break_before_round_closing_after_curly = "'}'", + remove_line_breaks_in_fun_dec = "FUNCTION", + set_line_break_around_curly_curly = "'{'", + style_line_break_around_curly = "'{'", + add_line_break_after_pipe = "SPECIAL-PIPE" + ), + tokens = list( + resolve_semicolon = "';'", + add_brackets_in_pipe = "SPECIAL-PIPE", + # before 3.6, these assignments are not wrapped into top level expression + # and `text` supplied to transformers_drop() is "", so it appears to not + # 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") + ) + ) + + if (getRversion() < 3.6) { + transformers_drop$token$force_assignment_op <- NULL + } + style_guide_name <- "styler::tidyverse_style@https://github.com/r-lib" create_style_guide( # transformer functions @@ -188,7 +239,8 @@ tidyverse_style <- function(scope = "tokens", reindention = reindention, style_guide_name = style_guide_name, style_guide_version = styler_version, - more_specs_style_guide = args + more_specs_style_guide = args, + transformers_drop = transformers_drop ) } @@ -231,6 +283,14 @@ tidyverse_style <- function(scope = "tokens", #' they will yield generic code and we loose the specific value of `arg` (see #' [styler::cache_make_key()]), even when unquoting these inputs with `!!` #' beforehand in `purrr::partial()`. +#' @param transformers_drop A list specifying under which conditions +#' transformer functions can be dropped since they have no effect on the +#' code to format, most easily constructed with +#' [specify_transformers_drop()]. This is argument experimental and may +#' change in future releases without prior notification. It was mainly +#' introduced to improve speed. Listing transformers here that occur almost +#' always in code does not make sense because the process of excluding them +#' also takes some time. #' @examples #' set_line_break_before_curly_opening <- function(pd_flat) { #' op <- pd_flat$token %in% "'{'" @@ -257,24 +317,89 @@ create_style_guide <- function(initialize = default_style_guide_attributes, reindention = tidyverse_reindention(), style_guide_name = NULL, style_guide_version = NULL, - more_specs_style_guide = NULL) { - lst( + more_specs_style_guide = NULL, + transformers_drop = specify_transformers_drop()) { + list( # transformer functions - initialize = lst(initialize), - line_break, - space, - token, - indention, + initialize = list(initialize = initialize), + line_break = line_break, + space = space, + token = token, + indention = indention, # transformer options - use_raw_indention, - reindention, - style_guide_name, - style_guide_version, - more_specs_style_guide + use_raw_indention = use_raw_indention, + reindention = reindention, + style_guide_name = style_guide_name, + style_guide_version = style_guide_version, + more_specs_style_guide = more_specs_style_guide, + transformers_drop = transformers_drop ) %>% map(compact) } +#' Specify which tokens must be absent for a transformer to be dropped +#' +#' `{styler}` can remove transformer functions safely removed from the list of +#' transformers to be applied on every *nest* with [transformers_drop()] if the +#' tokens that trigger a manipulation of the parse data are absent in the text +#' to style. `specify_transformers_drop()` helps you specify these +#' conditions. +#' +#' Note that the negative formulation (must be absent in order to be dropped) +#' means that when you add a new rule and you forget +#' to add a rule for when to drop it, it will not be dropped. If we required to +#' specify the complement (which tokens must be present for the transformer to +#' be kept), the transformer would be silently removed, which is less save. +#' @param spaces,indention,line_breaks,tokens Each a list (or `NULL`) where +#' the name of each element is the concerning transformer, the value is an +#' unnamed vector with tokens that match the rule. See 'Examples'. +#' +#' @section Warning: +#' It is the responsibility of the developer to ensure expected behavior, in +#' particular that: +#' * the name of the supplied dropping criteria matches the name of the +#' transformer function. +#' * the dropping criteria (name + token) reflects correctly under which +#' circumstances the transformer does not have an impact on styling and can +#' therefore be safely removed without affecting the styling outcome. +#' +#' You can use the unexported function [test_transformers_drop()] for some +#' checks. +#' @examples +#' dropping <- specify_transformers_drop( +#' spaces = c(remove_space_after_excl = "'!'") +#' ) +#' style_guide <- create_style_guide( +#' space = list(remove_space_after_excl = styler:::remove_space_after_excl), +#' transformers_drop = dropping +#' ) +#' # transformers_drop() will remove the transformer when the code does not +#' # contain an exclamation mark +#' style_guide_with_some_transformers_dropped <- styler:::transformers_drop( +#' "x <- 3;2", style_guide +#' ) +#' setdiff( +#' names(style_guide$space), +#' names(style_guide_with_some_transformers_dropped) +#' ) +#' # note that dropping all transformers of a scope means that this scope +#' # has an empty named list for this scope +#' style_guide_with_some_transformers_dropped$space +#' # this is not the same as if this scope was never specified. +#' tidyverse_style(scope = "none")$space +#' # Hence, styler should check for length 0 to decide if a scope is present or +#' # not, not via `is.null()` and we can use the `is.null()` check to see if +#' # this scope was initially required by the user. +#' @export +specify_transformers_drop <- function(spaces = NULL, + indention = NULL, + line_breaks = NULL, + tokens = NULL) { + list( + space = spaces, indention = indention, line_break = line_breaks, + token = tokens + ) +} #' Specify what is re-indented how #' @@ -302,10 +427,10 @@ NULL specify_reindention <- function(regex_pattern = NULL, indention = 0, comments_only = TRUE) { - lst( - regex_pattern, - indention, - comments_only + list( + regex_pattern = regex_pattern, + indention = indention, + comments_only = comments_only ) } @@ -381,9 +506,9 @@ specify_math_token_spacing <- function(zero = "'^'", one = c("'+'", "'-'", "'*'", "'/'")) { assert_tokens(c(one, zero)) - lst( + list( one = setdiff(c(math_token, one), zero), - zero + zero = zero ) } diff --git a/R/testing.R b/R/testing.R index 6d7c90883..b5b00f0d1 100644 --- a/R/testing.R +++ b/R/testing.R @@ -341,3 +341,28 @@ fresh_testthat_cache <- function() { cache_more_specs_default <- function() { cache_more_specs(include_roxygen_examples = TRUE, base_indention = 0) } + +#' Test `transformers_drop` for consistency +#' +#' Check if the argument `transformers_drop` in [create_style_guide()] is +#' consistent with the transformers specified in that function. +#' @param transformers The output of [create_style_guide()] we want to test. +#' @keywords internal +test_transformers_drop <- function(transformers) { + scopes <- intersect( + names(transformers$transformers_drop), + names(transformers) + ) + + purrr::walk2(transformers$transformers_drop, transformers[scopes], function(x, y) { + # all x must be in y. select the x that are not in y + diff <- setdiff(names(x), names(y)) + if (length(diff) > 0) { + rlang::abort(paste( + "transformers_drop specifies exclusion rules for transformers that ", + "are not in the style guilde. Please add the rule to the style guide ", + "or remove the dropping rules:", paste(diff, collapse = ", ") + )) + } + }) +} diff --git a/R/transform-code.R b/R/transform-code.R index eefcaba9d..eeef0856c 100644 --- a/R/transform-code.R +++ b/R/transform-code.R @@ -64,7 +64,7 @@ separate_chunks <- function(lines, filetype) { c(1, r_raw_chunks$ends), c(r_raw_chunks$starts, length(lines)), ~ lines[seq2(.x, .y)] ) - lst(r_chunks, text_chunks) + list(r_chunks = r_chunks, text_chunks = text_chunks) } #' Identifies raw Rmd or Rnw code chunks diff --git a/R/transform-files.R b/R/transform-files.R index 7d266b3b9..cccae05ec 100644 --- a/R/transform-files.R +++ b/R/transform-files.R @@ -169,6 +169,7 @@ parse_transform_serialize_roxygen <- function(text, transformers, base_indention flatten_chr() } + #' Split text into roxygen and non-roxygen example segments #' #' @param text Roxygen comments @@ -186,7 +187,7 @@ parse_transform_serialize_roxygen <- function(text, transformers, base_indention #' @keywords internal split_roxygen_segments <- function(text, roxygen_examples) { if (is.null(roxygen_examples)) { - return(lst(separated = list(text), selectors = NULL)) + return(list(separated = list(text), selectors = NULL)) } all_lines <- seq2(1L, length(text)) active_segment <- as.integer(all_lines %in% roxygen_examples) @@ -194,7 +195,7 @@ split_roxygen_segments <- function(text, roxygen_examples) { separated <- split(text, factor(segment_id)) restyle_selector <- ifelse(roxygen_examples[1] == 1L, odd_index, even_index) - lst(separated, selectors = restyle_selector(separated)) + list(separated = separated, selectors = restyle_selector(separated)) } #' Parse, transform and serialize text @@ -217,18 +218,21 @@ parse_transform_serialize_r <- function(text, text <- assert_text(text) pd_nested <- compute_parse_data_nested(text, transformers, more_specs) - blank_lines_to_next_expr <- find_blank_lines_to_next_block(pd_nested) if (nrow(pd_nested) == 0) { if (warn_empty) { warn("Text to style did not contain any tokens. Returning empty string.") } return("") } + transformers <- transformers_drop( + if (getRversion() < 3.4) text else pd_nested$text[!pd_nested$is_cached], + transformers + ) text_out <- pd_nested %>% split(pd_nested$block) %>% unname() %>% - map2(blank_lines_to_next_expr, + map2(find_blank_lines_to_next_block(pd_nested), parse_transform_serialize_r_block, transformers = transformers, base_indention = base_indention @@ -245,6 +249,38 @@ parse_transform_serialize_r <- function(text, text_out } + +#' Remove transformers that are not needed +#' +#' The goal is to speed up styling by removing all rules that are only +#' applicable in contexts that don't occur often, e.g. for most code, we don't +#' expect ";" to be in it, so we don't need to apply `resolve_semicolon()` on +#' every *nest*. +#' @param text Text to parse. Can also be the column `text` of the output of +#' [compute_parse_data_nested()], where each element is a token (instead of a +#' line). +#' @param transformers the transformers. +#' @keywords internal +#' @seealso specify_transformers_drop +transformers_drop <- function(text, transformers) { + is_colon <- text == ";" + if (any(is_colon)) { + # ; can only be parsed when on the same line as other token, not the case + # here since text is output of compute_parse_data_nested. + text <- c(text[!is_colon], "1;") + } + token <- unique(tokenize(text)$token) + for (scope in c("line_break", "space", "token", "indention")) { + rules <- transformers$transformers_drop[[scope]] + for (rule in names(rules)) { + if (!any(rules[[rule]] %in% token)) { + transformers[[scope]][rule] <- NULL + } + } + } + transformers +} + #' Apply transformers to a parse table #' #' The column `multi_line` is updated (after the line break information is @@ -273,7 +309,7 @@ apply_transformers <- function(pd_nested, transformers) { pd_nested, c( transformers$initialize, transformers$line_break, set_multi_line, - if (!is.null(transformers$line_break)) update_newlines + if (length(transformers$line_break) != 0) update_newlines ) ) @@ -303,7 +339,7 @@ apply_transformers <- function(pd_nested, transformers) { #' Needed for reverse engineering the scope. #' @keywords internal can_verify_roundtrip <- function(transformers) { - is.null(transformers$token) + length(transformers$token) == 0 } #' Verify the styling diff --git a/inst/WORDLIST b/inst/WORDLIST index 957c3a8b0..0b4fe44db 100644 --- a/inst/WORDLIST +++ b/inst/WORDLIST @@ -69,6 +69,7 @@ href http https icloud +impl infinitively initializer innode @@ -193,6 +194,7 @@ tidyeval tidyr tidyverse Tidyverse +tokenized travis tryCatch tryGugus diff --git a/man/create_style_guide.Rd b/man/create_style_guide.Rd index bb07f00e3..ef1e8add1 100644 --- a/man/create_style_guide.Rd +++ b/man/create_style_guide.Rd @@ -14,7 +14,8 @@ create_style_guide( reindention = tidyverse_reindention(), style_guide_name = NULL, style_guide_version = NULL, - more_specs_style_guide = NULL + more_specs_style_guide = NULL, + transformers_drop = specify_transformers_drop() ) } \arguments{ @@ -55,6 +56,15 @@ such functions are converted to characters in \code{\link[=cache_make_key]{cache they will yield generic code and we loose the specific value of \code{arg} (see \code{\link[=cache_make_key]{cache_make_key()}}), even when unquoting these inputs with \verb{!!} beforehand in \code{purrr::partial()}.} + +\item{transformers_drop}{A list specifying under which conditions +transformer functions can be dropped since they have no effect on the +code to format, most easily constructed with +\code{\link[=specify_transformers_drop]{specify_transformers_drop()}}. This is argument experimental and may +change in future releases without prior notification. It was mainly +introduced to improve speed. Listing transformers here that occur almost +always in code does not make sense because the process of excluding them +also takes some time.} } \description{ This is a helper function to create a style guide, which is technically diff --git a/man/specify_transformers_drop.Rd b/man/specify_transformers_drop.Rd new file mode 100644 index 000000000..e9069cc33 --- /dev/null +++ b/man/specify_transformers_drop.Rd @@ -0,0 +1,74 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/style-guides.R +\name{specify_transformers_drop} +\alias{specify_transformers_drop} +\title{Specify which tokens must be absent for a transformer to be dropped} +\usage{ +specify_transformers_drop( + spaces = NULL, + indention = NULL, + line_breaks = NULL, + tokens = NULL +) +} +\arguments{ +\item{spaces, indention, line_breaks, tokens}{Each a list (or \code{NULL}) where +the name of each element is the concerning transformer, the value is an +unnamed vector with tokens that match the rule. See 'Examples'.} +} +\description{ +\code{{styler}} can remove transformer functions safely removed from the list of +transformers to be applied on every \emph{nest} with \code{\link[=transformers_drop]{transformers_drop()}} if the +tokens that trigger a manipulation of the parse data are absent in the text +to style. \code{specify_transformers_drop()} helps you specify these +conditions. +} +\details{ +Note that the negative formulation (must be absent in order to be dropped) +means that when you add a new rule and you forget +to add a rule for when to drop it, it will not be dropped. If we required to +specify the complement (which tokens must be present for the transformer to +be kept), the transformer would be silently removed, which is less save. +} +\section{Warning}{ + +It is the responsibility of the developer to ensure expected behavior, in +particular that: +\itemize{ +\item the name of the supplied dropping criteria matches the name of the +transformer function. +\item the dropping criteria (name + token) reflects correctly under which +circumstances the transformer does not have an impact on styling and can +therefore be safely removed without affecting the styling outcome. +} + +You can use the unexported function \code{\link[=test_transformers_drop]{test_transformers_drop()}} for some +checks. +} + +\examples{ +dropping <- specify_transformers_drop( + spaces = c(remove_space_after_excl = "'!'") +) +style_guide <- create_style_guide( + space = list(remove_space_after_excl = styler:::remove_space_after_excl), + transformers_drop = dropping +) +# transformers_drop() will remove the transformer when the code does not +# contain an exclamation mark +style_guide_with_some_transformers_dropped <- styler:::transformers_drop( + "x <- 3;2", style_guide +) +setdiff( + names(style_guide$space), + names(style_guide_with_some_transformers_dropped) +) +# note that dropping all transformers of a scope means that this scope +# has an empty named list for this scope +style_guide_with_some_transformers_dropped$space +# this is not the same as if this scope was never specified. +tidyverse_style(scope = "none")$space +# Hence, styler should check for length 0 to decide if a scope is present or +# not, not via `is.null()` and we can use the `is.null()` check to see if +# this scope was initially required by the user. +} diff --git a/man/test_transformers_drop.Rd b/man/test_transformers_drop.Rd new file mode 100644 index 000000000..bd2bfa381 --- /dev/null +++ b/man/test_transformers_drop.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/testing.R +\name{test_transformers_drop} +\alias{test_transformers_drop} +\title{Test \code{transformers_drop} for consistency} +\usage{ +test_transformers_drop(transformers) +} +\arguments{ +\item{transformers}{The output of \code{\link[=create_style_guide]{create_style_guide()}} we want to test.} +} +\description{ +Check if the argument \code{transformers_drop} in \code{\link[=create_style_guide]{create_style_guide()}} is +consistent with the transformers specified in that function. +} +\keyword{internal} diff --git a/man/transformers_drop.Rd b/man/transformers_drop.Rd new file mode 100644 index 000000000..19623db73 --- /dev/null +++ b/man/transformers_drop.Rd @@ -0,0 +1,25 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/transform-files.R +\name{transformers_drop} +\alias{transformers_drop} +\title{Remove transformers that are not needed} +\usage{ +transformers_drop(text, transformers) +} +\arguments{ +\item{text}{Text to parse. Can also be the column \code{text} of the output of +\code{\link[=compute_parse_data_nested]{compute_parse_data_nested()}}, where each element is a token (instead of a +line).} + +\item{transformers}{the transformers.} +} +\description{ +The goal is to speed up styling by removing all rules that are only +applicable in contexts that don't occur often, e.g. for most code, we don't +expect ";" to be in it, so we don't need to apply \code{resolve_semicolon()} on +every \emph{nest}. +} +\seealso{ +specify_transformers_drop +} +\keyword{internal} diff --git a/tests/testthat/test-serialize_tests.R b/tests/testthat/test-serialize_tests.R index 19faf3f9b..77433ee1d 100644 --- a/tests/testthat/test-serialize_tests.R +++ b/tests/testthat/test-serialize_tests.R @@ -26,3 +26,26 @@ test_that("properly detects match", { "identical" ) }) + +test_that('detects non-matching style guides', { + sg <- create_style_guide( + space = list( + a1 = function(...) NULL, + b1 = function(... ) 1 + ), + transformers_drop = specify_transformers_drop( + spaces = c(a1 = "'+'") + ) + ) + expect_silent(test_transformers_drop(sg)) + + sg <- create_style_guide( + space = list( + a1 = function(...) NULL + ), + transformers_drop = specify_transformers_drop( + spaces = c(a2 = "'+'") + ) + ) + expect_error(test_transformers_drop(sg)) +}) diff --git a/tests/testthat/test-transformers-drop.R b/tests/testthat/test-transformers-drop.R new file mode 100644 index 000000000..a93aa4921 --- /dev/null +++ b/tests/testthat/test-transformers-drop.R @@ -0,0 +1,147 @@ +# c/cp from remove_space_after_excl but for self-containement repeated +remove_space_after_excl_ <- function(pd_flat) { + excl <- (pd_flat$token == "'!'") & + (pd_flat$token_after != "'!'") & + (pd_flat$newlines == 0L) + pd_flat$spaces[excl] <- 0L + pd_flat +} + +t <- create_style_guide( + space = lst(remove_space_after_excl_), + transformers_drop = specify_transformers_drop( + spaces = list(remove_space_after_excl_ = c("'!'")) + ), + style_guide_name = "styler::t@https://github.com/r-lib", + style_guide_version = as.character(packageVersion("styler")) +) + +t_no_drop <- create_style_guide( + space = lst(remove_space_after_excl_), + transformers_drop = NULL, +) + +t_empty_drop1 <- create_style_guide( + space = lst(remove_space_after_excl_), + transformers_drop = list(space = list()), +) + +t_empty_drop2 <- create_style_guide( + space = lst(remove_space_after_excl_), + transformers_drop = list(), +) + +test_that("transformers are not removed if they are used", { + t_new <- transformers_drop( + "!x", t + ) + expect_equal(t_new, t) +}) + +test_that("transformers are removed if they are unused", { + t_fun <- transformers_drop( + "x", t + ) + t_manual <- t + t_manual$space$remove_space_after_excl_ <- NULL + expect_equal(t_fun, t_manual) +}) + +test_that("tidyverse transformers are correctly named", { + # test that all dropping rules match an actual rule in the style guide + expect_silent( + test_transformers_drop(tidyverse_style()) + ) +}) + +test_that("tidyverse transformers are correctly dropped", { + # TODO maybe there is a more minimal test than this. + t_style <- tidyverse_style() + t_fun <- transformers_drop("x", t_style) + + names_line_break <- c( + "set_line_break_around_comma_and_or", + "set_line_break_after_assignment", + "set_line_break_after_opening_if_call_is_multi_line", + "set_line_break_before_closing_call", + "remove_line_break_in_fun_call", + "set_linebreak_after_ggplot2_plus" + ) + expect_setequal(names(t_fun$line_break), names_line_break) + + names_spaces <- c( + "remove_space_before_closing_paren", + "remove_space_before_opening_paren", + "remove_space_before_comma", + "spacing_around_op", + "remove_space_after_opening_paren", + "set_space_between_levels" + ) + + expect_setequal(names(t_fun$space), names_spaces) + + names_indention <- c("indent_braces", "indent_op", "indent_without_paren") + expect_setequal(names(t_fun$indention), names_indention) + + names_tokens <- c( + "fix_quotes", + if (getRversion() < 3.6) "force_assignment_op", + "remove_terminal_token_before_and_after" + ) + expect_setequal(names(t_fun$token), names_tokens) +}) + + +test_that("if no transformers_drop is specified, no transformer is removed and no error issued", { + t_fun <- transformers_drop( + "x", t_no_drop + ) + expect_equal(t_fun, t_no_drop) + + t_fun <- transformers_drop( + "x", t_empty_drop1 + ) + expect_equal(t_fun, t_empty_drop1) + + t_fun <- transformers_drop( + "x", t_empty_drop2 + ) + expect_equal(t_fun, t_empty_drop2) +}) + +test_that('semi-colon is parsed without error', { + expect_equal( + transformers_drop(c("!a", ";", "b"), t), + t + ) +}) + + +test_that('can handle old style guide without transformer object', { + t_new <- t + t_new$transformers_drop <- NULL + expect_error( + transformers_drop(c("!a", ";", "b"), t_new), + NA + ) + expect_error( + style_text('1;3', transformers = t_new), + NA + ) +}) + +test_that("can handle default", { + t_no_drop <- create_style_guide( + space = lst(remove_space_after_excl_), + style_guide_name = "styler::t@https://github.com/r-lib", + style_guide_version = as.character(packageVersion("styler")) + ) + expect_error( + transformers_drop(c("!a", ";", "b"), t_no_drop), + NA + ) + expect_error( + style_text('a =2 ', transformers = t_no_drop), + NA + ) +})