diff --git a/API b/API index 4d65d19be..46b34bbcd 100644 --- a/API +++ b/API @@ -6,8 +6,22 @@ cache_activate(cache_name = NULL, verbose = !getOption("styler.quiet", FALSE)) cache_clear(cache_name = NULL, ask = TRUE) cache_deactivate(verbose = !getOption("styler.quiet", FALSE)) cache_info(cache_name = NULL, format = "both") +compute_parse_data_nested(text, transformers = tidyverse_style(), more_specs = 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(), indent_character = " ") default_style_guide_attributes(pd_flat) +is_asymmetric_tilde_expr(pd) +is_comment(pd) +is_conditional_expr(pd) +is_curly_expr(pd) +is_for_expr(pd) +is_function_call(pd) +is_function_declaration(pd) +is_symmetric_tilde_expr(pd) +is_tilde_expr(pd, tilde_pos = c(1L, 2L)) +is_while_expr(pd) +next_non_comment(pd, pos) +previous_non_comment(pd, pos) +scope_normalize(scope, name = substitute(scope)) specify_math_token_spacing(zero = "'^'", one = c("'+'", "'-'", "'*'", "'/'")) specify_reindention(regex_pattern = NULL, indention = 0L, comments_only = TRUE) specify_transformers_drop(spaces = NULL, indention = NULL, line_breaks = NULL, tokens = NULL) @@ -17,7 +31,7 @@ style_pkg(pkg = ".", ..., style = tidyverse_style, transformers = style(...), fi style_text(text, ..., style = tidyverse_style, transformers = style(...), include_roxygen_examples = TRUE, base_indention = 0L) tidyverse_math_token_spacing() tidyverse_reindention() -tidyverse_style(scope = "tokens", strict = TRUE, indent_by = 2, start_comments_with_one_space = FALSE, reindention = tidyverse_reindention(), math_token_spacing = tidyverse_math_token_spacing()) +tidyverse_style(scope = "tokens", strict = TRUE, indent_by = 2L, start_comments_with_one_space = FALSE, reindention = tidyverse_reindention(), math_token_spacing = tidyverse_math_token_spacing()) ## Foreign S3 methods diff --git a/NAMESPACE b/NAMESPACE index 4d1a3ba01..42f8c5ba2 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -5,8 +5,22 @@ export(cache_activate) export(cache_clear) export(cache_deactivate) export(cache_info) +export(compute_parse_data_nested) export(create_style_guide) export(default_style_guide_attributes) +export(is_asymmetric_tilde_expr) +export(is_comment) +export(is_conditional_expr) +export(is_curly_expr) +export(is_for_expr) +export(is_function_call) +export(is_function_declaration) +export(is_symmetric_tilde_expr) +export(is_tilde_expr) +export(is_while_expr) +export(next_non_comment) +export(previous_non_comment) +export(scope_normalize) export(specify_math_token_spacing) export(specify_reindention) export(specify_transformers_drop) diff --git a/R/detect-alignment.R b/R/detect-alignment.R index 016388d5f..780ae1da1 100644 --- a/R/detect-alignment.R +++ b/R/detect-alignment.R @@ -31,7 +31,7 @@ #' list(styler.cache_name = NULL), # temporarily deactivate cache #' { #' transformers <- tidyverse_style() -#' pd_nested <- styler:::compute_parse_data_nested(c( +#' pd_nested <- compute_parse_data_nested(c( #' "call(", #' " ab = 1L,", #' " a = 2", diff --git a/R/expr-is.R b/R/expr-is.R index f1021fd06..c4e239fbd 100644 --- a/R/expr-is.R +++ b/R/expr-is.R @@ -1,13 +1,25 @@ -#' Check whether a parse table corresponds to a certain expression +#' What is a parse table representing? #' -#' @param pd A parse table. +#' Check whether a parse table corresponds to a certain expression. #' @name pd_is +#' +#' @param pd A parse table. +#' @param tilde_pos Integer vector indicating row-indices that should be +#' checked for tilde. See 'Details'. +#' +#' @family third-party style guide helpers #' @keywords internal NULL -#' @describeIn pd_is Checks whether `pd` contains an expression wrapped in -#' curly brackets. -#' @keywords internal +#' @describeIn pd_is Checks whether `pd` contains an expression wrapped in curly brackets. +#' @examples +#' code <- "if (TRUE) { 1 }" +#' pd <- compute_parse_data_nested(code) +#' is_curly_expr(pd) +#' child_of_child <- pd$child[[1]]$child[[5]] +#' is_curly_expr(child_of_child) +#' +#' @export is_curly_expr <- function(pd) { if (is.null(pd)) { return(FALSE) @@ -15,24 +27,46 @@ is_curly_expr <- function(pd) { pd$token[1L] == "'{'" } +#' @describeIn pd_is Checks whether `pd` contains a `for` loop. +#' @examples +#' code <- "for (i in 1:5) print(1:i)" +#' pd <- compute_parse_data_nested(code) +#' is_for_expr(pd) +#' is_for_expr(pd$child[[1]]) +#' +#' @export is_for_expr <- function(pd) { pd$token[1L] == "FOR" } #' @describeIn pd_is Checks whether `pd` contains is a conditional expression. -#' @keywords internal -is_cond_expr <- function(pd) { +#' @examples +#' code <- "if (TRUE) x <- 1 else x <- 0" +#' pd <- compute_parse_data_nested(code) +#' is_conditional_expr(pd) +#' is_conditional_expr(pd$child[[1]]) +#' +#' @export +is_conditional_expr <- function(pd) { pd$token[1L] == "IF" } -#' @describeIn pd_is Checks whether `pd` contains is a while loop. -#' @keywords internal +#' @describeIn pd_is Checks whether `pd` contains a `while` loop. +#' @export is_while_expr <- function(pd) { pd$token[1L] == "WHILE" } + #' @describeIn pd_is Checks whether `pd` is a function call. -#' @keywords internal +#' @examples +#' code <- "x <- list(1:3)" +#' pd <- compute_parse_data_nested(code) +#' is_function_call(pd) +#' child_of_child <- pd$child[[1]]$child[[3]] +#' is_function_call(child_of_child) +#' +#' @export is_function_call <- function(pd) { if (is.null(pd)) { return(FALSE) @@ -44,8 +78,15 @@ is_function_call <- function(pd) { } #' @describeIn pd_is Checks whether `pd` is a function declaration. -#' @keywords internal -is_function_dec <- function(pd) { +#' @examples +#' code <- "foo <- function() NULL" +#' pd <- compute_parse_data_nested(code) +#' is_function_declaration(pd) +#' child_of_child <- pd$child[[1]]$child[[3]] +#' is_function_declaration(child_of_child) +#' +#' @export +is_function_declaration <- function(pd) { if (is.null(pd)) { return(FALSE) } @@ -53,7 +94,12 @@ is_function_dec <- function(pd) { } #' @describeIn pd_is Checks for every token whether or not it is a comment. -#' @keywords internal +#' @examples +#' code <- "x <- 1 # TODO: check value" +#' pd <- compute_parse_data_nested(code) +#' is_comment(pd) +#' +#' @export is_comment <- function(pd) { if (is.null(pd)) { return(FALSE) @@ -61,20 +107,19 @@ is_comment <- function(pd) { pd$token == "COMMENT" } - - -#' Check whether a parse table contains a tilde -#' -#' -#' @param pd A parse table. -#' @param tilde_pos Integer vector indicating row-indices that should be -#' checked for tilde. See 'Details'. -#' +#' @describeIn pd_is Checks whether `pd` contains a tilde. #' @details #' A tilde is on the top row in the parse table if it is an asymmetric tilde #' expression (like `~column`), in the second row if it is a symmetric tilde #' expression (like `a~b`). -#' @keywords internal +#' @examples +#' code <- "lm(wt ~ mpg, mtcars)" +#' pd <- compute_parse_data_nested(code) +#' is_tilde_expr(pd$child[[1]]$child[[3]]) +#' is_symmetric_tilde_expr(pd$child[[1]]$child[[3]]) +#' is_asymmetric_tilde_expr(pd$child[[1]]$child[[3]]) +#' +#' @export is_tilde_expr <- function(pd, tilde_pos = c(1L, 2L)) { if (is.null(pd) || nrow(pd) == 1L) { return(FALSE) @@ -82,18 +127,20 @@ is_tilde_expr <- function(pd, tilde_pos = c(1L, 2L)) { any(pd$token[tilde_pos] == "'~'") } -#' @rdname is_tilde_expr +#' @describeIn pd_is If `pd` contains a tilde, checks whether it is asymmetrical. +#' @export is_asymmetric_tilde_expr <- function(pd) { is_tilde_expr(pd, tilde_pos = 1L) } -#' @rdname is_tilde_expr +#' @describeIn pd_is If `pd` contains a tilde, checks whether it is symmetrical. +#' @export is_symmetric_tilde_expr <- function(pd) { is_tilde_expr(pd, tilde_pos = 2L) } is_subset_expr <- function(pd) { - if (is.null(pd) || nrow(pd) == 1) { + if (is.null(pd) || nrow(pd) == 1L) { return(FALSE) } pd$token[2L] %in% subset_token_opening @@ -152,7 +199,7 @@ contains_else_expr_that_needs_braces <- function(pd) { non_comment_after_else <- next_non_comment(pd, else_idx) sub_expr <- pd$child[[non_comment_after_else]] # needs braces if NOT if_condition, NOT curly expr - !is_cond_expr(sub_expr) && !is_curly_expr(sub_expr) + !is_conditional_expr(sub_expr) && !is_curly_expr(sub_expr) } else { FALSE } diff --git a/R/initialize.R b/R/initialize.R index d8ca406d2..c130ded0b 100644 --- a/R/initialize.R +++ b/R/initialize.R @@ -9,7 +9,7 @@ #' list(styler.cache_name = NULL), # temporarily deactivate cache #' { #' string_to_format <- "call( 3)" -#' pd <- styler:::compute_parse_data_nested(string_to_format) +#' pd <- compute_parse_data_nested(string_to_format) #' styler:::pre_visit_one(pd, default_style_guide_attributes) #' } #' ) diff --git a/R/nest.R b/R/nest.R index d9cb0ea5e..0b1f60a60 100644 --- a/R/nest.R +++ b/R/nest.R @@ -6,10 +6,17 @@ #' @return A nested parse table. See [tokenize()] for details on the columns #' of the parse table. #' @importFrom purrr when -#' @keywords internal +#' @examples +#' code <- " +#' ab <- 1L # some comment +#' abcdef <- 2L +#' " +#' writeLines(code) +#' compute_parse_data_nested(code) +#' @export compute_parse_data_nested <- function(text, - transformers, - more_specs) { + transformers = tidyverse_style(), + more_specs = NULL) { parse_data <- text_to_flat_pd(text, transformers, more_specs = more_specs) env_add_stylerignore(parse_data) parse_data$child <- rep(list(NULL), length(parse_data$text)) diff --git a/R/nested-to-tree.R b/R/nested-to-tree.R index 46377bf89..f0bde0e8c 100644 --- a/R/nested-to-tree.R +++ b/R/nested-to-tree.R @@ -36,7 +36,7 @@ create_tree_from_pd_with_default_style_attributes <- function(pd, #' list(styler.cache_name = NULL), # temporarily deactivate cache #' { #' code <- "a <- function(x) { if(x > 1) { 1+1 } else {x} }" -#' nested_pd <- styler:::compute_parse_data_nested(code) +#' nested_pd <- compute_parse_data_nested(code) #' initialized <- styler:::pre_visit_one( #' nested_pd, default_style_guide_attributes #' ) diff --git a/R/rules-indention.R b/R/rules-indention.R index e6ac2d5ce..f21583bcd 100644 --- a/R/rules-indention.R +++ b/R/rules-indention.R @@ -18,7 +18,7 @@ indent_braces <- function(pd, indent_by) { #' @seealso set_unindention_child update_indention_ref_fun_dec #' @keywords internal unindent_fun_dec <- function(pd) { - if (is_function_dec(pd)) { + if (is_function_declaration(pd)) { idx_closing_brace <- which(pd$token %in% "')'") fun_dec_head <- seq2(2L, idx_closing_brace) pd$indent[fun_dec_head] <- 0L diff --git a/R/rules-line-breaks.R b/R/rules-line-breaks.R index 705e52a2e..58f21fb36 100644 --- a/R/rules-line-breaks.R +++ b/R/rules-line-breaks.R @@ -98,7 +98,7 @@ set_line_break_before_curly_opening <- function(pd) { should_not_be_on_same_line_idx <- line_break_to_set_idx[ should_not_be_on_same_line ] - if (is_function_dec(pd)) { + if (is_function_declaration(pd)) { should_not_be_on_same_line_idx <- setdiff( 1L + should_not_be_on_same_line_idx, nrow(pd) ) @@ -228,7 +228,7 @@ remove_line_break_before_round_closing_after_curly <- function(pd) { } remove_line_breaks_in_fun_dec <- function(pd) { - if (is_function_dec(pd)) { + if (is_function_declaration(pd)) { round_after <- ( pd$token == "')'" | pd$token_before == "'('" ) & diff --git a/R/rules-spaces.R b/R/rules-spaces.R index d28784d96..271a00a59 100644 --- a/R/rules-spaces.R +++ b/R/rules-spaces.R @@ -22,7 +22,7 @@ set_space_around_op <- function(pd_flat, strict) { !getOption("styler.ignore_alignment", FALSE) && ( (is_function_call(pd_flat) && sum_lag_newlines > 2L) || - (is_function_dec(pd_flat) && sum_lag_newlines > 1L) + (is_function_declaration(pd_flat) && sum_lag_newlines > 1L) ) && any(pd_flat$token %in% c("EQ_SUB", "','", "EQ_FORMALS")) ) { @@ -96,10 +96,8 @@ style_space_around_token <- function(pd_flat, pd_flat$spaces[idx_before] <- level_before pd_flat$spaces[idx_after] <- level_after } else { - pd_flat$spaces[idx_before] <- - pmax(pd_flat$spaces[idx_before], level_before) - pd_flat$spaces[idx_after] <- - pmax(pd_flat$spaces[idx_after], level_after) + pd_flat$spaces[idx_before] <- pmax(pd_flat$spaces[idx_before], level_before) + pd_flat$spaces[idx_after] <- pmax(pd_flat$spaces[idx_after], level_after) } pd_flat } @@ -110,12 +108,15 @@ style_space_around_tilde <- function(pd_flat, strict) { strict, "'~'", level_before = 1L, level_after = 1L ) - } else if (is_asymmetric_tilde_expr(pd_flat)) { + } + + if (is_asymmetric_tilde_expr(pd_flat)) { pd_flat <- style_space_around_token(pd_flat, strict = TRUE, "'~'", level_before = 1L, level_after = as.integer(nrow(pd_flat$child[[2L]]) > 1L) ) } + pd_flat } @@ -286,7 +287,7 @@ start_comments_with_space <- function(pd, force_one = FALSE) { comments$text ) %>% trimws("right") - pd$short[is_comment] <- substr(pd$text[is_comment], 1, 5) + pd$short[is_comment] <- substr(pd$text[is_comment], 1L, 5L) pd } @@ -345,20 +346,16 @@ remove_space_after_fun_dec <- function(pd_flat) { } remove_space_around_colons <- function(pd_flat) { - one_two_or_three_col_after <- - pd_flat$token %in% c("':'", "NS_GET_INT", "NS_GET") - - one_two_or_three_col_before <- - lead(one_two_or_three_col_after, default = FALSE) + one_two_or_three_col_after <- pd_flat$token %in% c("':'", "NS_GET_INT", "NS_GET") + one_two_or_three_col_before <- lead(one_two_or_three_col_after, default = FALSE) - col_around <- - one_two_or_three_col_before | one_two_or_three_col_after + col_around <- one_two_or_three_col_before | one_two_or_three_col_after pd_flat$spaces[col_around & (pd_flat$newlines == 0L)] <- 0L pd_flat } -#' Set space between EQ_SUB and "','" +#' Set space between `EQ_SUB` and `"','"` #' @param pd A parse table. #' @keywords internal set_space_between_eq_sub_and_comma <- function(pd) { diff --git a/R/rules-tokens.R b/R/rules-tokens.R index f8e5041bf..e6b33780f 100644 --- a/R/rules-tokens.R +++ b/R/rules-tokens.R @@ -71,10 +71,10 @@ add_brackets_in_pipe_one <- function(pd, pos) { wrap_if_else_while_for_fun_multi_line_in_curly <- function(pd, indent_by = 2L) { key_token <- when( pd, - is_cond_expr(.) ~ "')'", + is_conditional_expr(.) ~ "')'", is_while_expr(.) ~ "')'", is_for_expr(.) ~ "forcond", - is_function_dec(.) ~ "')'" + is_function_declaration(.) ~ "')'" ) if (length(key_token) > 0L) { pd <- pd %>% @@ -83,7 +83,7 @@ wrap_if_else_while_for_fun_multi_line_in_curly <- function(pd, indent_by = 2L) { space_after = as.integer(contains_else_expr(pd)) ) } - if (is_cond_expr(pd)) { + if (is_conditional_expr(pd)) { pd <- pd %>% wrap_else_multiline_curly(indent_by, space_after = 0L) } diff --git a/R/style-guides.R b/R/style-guides.R index 10f8fffb8..efa46b82f 100644 --- a/R/style-guides.R +++ b/R/style-guides.R @@ -65,7 +65,7 @@ NULL #' @export tidyverse_style <- function(scope = "tokens", strict = TRUE, - indent_by = 2, + indent_by = 2L, start_comments_with_one_space = FALSE, reindention = tidyverse_reindention(), math_token_spacing = tidyverse_math_token_spacing()) { @@ -477,8 +477,12 @@ tidyverse_reindention <- function() { #' @param scope A character vector of length one or a vector of class `AsIs`. #' @param name The name of the character vector to be displayed if the #' construction of the factor fails. -#' @keywords internal #' @importFrom rlang abort +#' @examples +#' scope_normalize(I("tokens")) +#' scope_normalize(I(c("indention", "tokens"))) +#' @family third-party style guide helpers +#' @export scope_normalize <- function(scope, name = substitute(scope)) { levels <- c("none", "spaces", "indention", "line_breaks", "tokens") if (!all((scope %in% levels))) { diff --git a/R/utils-navigate-nest.R b/R/utils-navigate-nest.R index c4c5e7432..0d2051467 100644 --- a/R/utils-navigate-nest.R +++ b/R/utils-navigate-nest.R @@ -1,9 +1,16 @@ - #' Find the index of the next or previous non-comment in a parse table. #' @param pd A parse table. #' @param pos The position of the token to start the search from. #' @importFrom rlang seq2 -#' @keywords internal +#' @examples +#' code <- "a <- # hi \n x %>% b()" +#' writeLines(code) +#' pd <- compute_parse_data_nested(code) +#' child <- pd$child[[1]] +#' previous_non_comment(child, 4L) +#' next_non_comment(child, 2L) +#' @family third-party style guide helpers +#' @export next_non_comment <- function(pd, pos) { if (length(pos) < 1 || is.na(pos) || pos >= nrow(pd)) { return(integer(0)) @@ -15,6 +22,7 @@ next_non_comment <- function(pd, pos) { setdiff(candidates, which(pd$token == "COMMENT"))[1L] } +#' @export #' @rdname next_non_comment previous_non_comment <- function(pd, pos) { if (length(pos) < 1 || is.na(pos) || pos > nrow(pd)) { @@ -51,7 +59,7 @@ previous_non_comment <- function(pd, pos) { #' withr::with_options( #' list(styler.cache_name = NULL), # temporarily deactivate cache #' { -#' pd <- styler:::compute_parse_data_nested("if (TRUE) f()") +#' pd <- compute_parse_data_nested("if (TRUE) f()") #' styler:::next_terminal(pd) #' } #' ) diff --git a/_pkgdown.yaml b/_pkgdown.yaml index 37239117c..ed50bc3f2 100644 --- a/_pkgdown.yaml +++ b/_pkgdown.yaml @@ -31,6 +31,11 @@ reference: desc: "Utilities to help manage the styler cache" - contents: - starts_with("cache") + - title: "Third-party style guide helpers" + desc: "Utilities for customizing styler for non-tidyverse style guides" + - contents: + - compute_parse_data_nested + - has_concept("third-party style guide helpers") - title: "Other" contents: - print.vertical diff --git a/man/compute_parse_data_nested.Rd b/man/compute_parse_data_nested.Rd index 17eae4c80..0c6f4768d 100644 --- a/man/compute_parse_data_nested.Rd +++ b/man/compute_parse_data_nested.Rd @@ -4,7 +4,11 @@ \alias{compute_parse_data_nested} \title{Obtain a nested parse table from a character vector} \usage{ -compute_parse_data_nested(text, transformers, more_specs) +compute_parse_data_nested( + text, + transformers = tidyverse_style(), + more_specs = NULL +) } \arguments{ \item{text}{The text to parse.} @@ -21,4 +25,11 @@ of the parse table. Parses \code{text} to a flat parse table and subsequently changes its representation into a nested parse table with \code{\link[=nest_parse_data]{nest_parse_data()}}. } -\keyword{internal} +\examples{ +code <- " +ab <- 1L # some comment +abcdef <- 2L +" +writeLines(code) +compute_parse_data_nested(code) +} diff --git a/man/create_node_from_nested_root.Rd b/man/create_node_from_nested_root.Rd index 2127abaf5..db4280645 100644 --- a/man/create_node_from_nested_root.Rd +++ b/man/create_node_from_nested_root.Rd @@ -26,7 +26,7 @@ if (rlang::is_installed("data.tree")) { list(styler.cache_name = NULL), # temporarily deactivate cache { code <- "a <- function(x) { if(x > 1) { 1+1 } else {x} }" - nested_pd <- styler:::compute_parse_data_nested(code) + nested_pd <- compute_parse_data_nested(code) initialized <- styler:::pre_visit_one( nested_pd, default_style_guide_attributes ) diff --git a/man/default_style_guide_attributes.Rd b/man/default_style_guide_attributes.Rd index 32b3e91e5..ec5805cbe 100644 --- a/man/default_style_guide_attributes.Rd +++ b/man/default_style_guide_attributes.Rd @@ -18,7 +18,7 @@ withr::with_options( list(styler.cache_name = NULL), # temporarily deactivate cache { string_to_format <- "call( 3)" - pd <- styler:::compute_parse_data_nested(string_to_format) + pd <- compute_parse_data_nested(string_to_format) styler:::pre_visit_one(pd, default_style_guide_attributes) } ) diff --git a/man/is_tilde_expr.Rd b/man/is_tilde_expr.Rd deleted file mode 100644 index 3f11f9453..000000000 --- a/man/is_tilde_expr.Rd +++ /dev/null @@ -1,29 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/expr-is.R -\name{is_tilde_expr} -\alias{is_tilde_expr} -\alias{is_asymmetric_tilde_expr} -\alias{is_symmetric_tilde_expr} -\title{Check whether a parse table contains a tilde} -\usage{ -is_tilde_expr(pd, tilde_pos = c(1L, 2L)) - -is_asymmetric_tilde_expr(pd) - -is_symmetric_tilde_expr(pd) -} -\arguments{ -\item{pd}{A parse table.} - -\item{tilde_pos}{Integer vector indicating row-indices that should be -checked for tilde. See 'Details'.} -} -\description{ -Check whether a parse table contains a tilde -} -\details{ -A tilde is on the top row in the parse table if it is an asymmetric tilde -expression (like \code{~column}), in the second row if it is a symmetric tilde -expression (like \code{a~b}). -} -\keyword{internal} diff --git a/man/next_non_comment.Rd b/man/next_non_comment.Rd index a607647a7..b66b1825c 100644 --- a/man/next_non_comment.Rd +++ b/man/next_non_comment.Rd @@ -17,4 +17,17 @@ previous_non_comment(pd, pos) \description{ Find the index of the next or previous non-comment in a parse table. } -\keyword{internal} +\examples{ +code <- "a <- # hi \n x \%>\% b()" +writeLines(code) +pd <- compute_parse_data_nested(code) +child <- pd$child[[1]] +previous_non_comment(child, 4L) +next_non_comment(child, 2L) +} +\seealso{ +Other third-party style guide helpers: +\code{\link{pd_is}}, +\code{\link{scope_normalize}()} +} +\concept{third-party style guide helpers} diff --git a/man/next_terminal.Rd b/man/next_terminal.Rd index 9ddaf7775..c332197de 100644 --- a/man/next_terminal.Rd +++ b/man/next_terminal.Rd @@ -40,7 +40,7 @@ next terminal withr::with_options( list(styler.cache_name = NULL), # temporarily deactivate cache { - pd <- styler:::compute_parse_data_nested("if (TRUE) f()") + pd <- compute_parse_data_nested("if (TRUE) f()") styler:::next_terminal(pd) } ) diff --git a/man/pd_is.Rd b/man/pd_is.Rd index e347f0d69..39e40c342 100644 --- a/man/pd_is.Rd +++ b/man/pd_is.Rd @@ -3,45 +3,118 @@ \name{pd_is} \alias{pd_is} \alias{is_curly_expr} -\alias{is_cond_expr} +\alias{is_for_expr} +\alias{is_conditional_expr} \alias{is_while_expr} \alias{is_function_call} -\alias{is_function_dec} +\alias{is_function_declaration} \alias{is_comment} -\title{Check whether a parse table corresponds to a certain expression} +\alias{is_tilde_expr} +\alias{is_asymmetric_tilde_expr} +\alias{is_symmetric_tilde_expr} +\title{What is a parse table representing?} \usage{ is_curly_expr(pd) -is_cond_expr(pd) +is_for_expr(pd) + +is_conditional_expr(pd) is_while_expr(pd) is_function_call(pd) -is_function_dec(pd) +is_function_declaration(pd) is_comment(pd) + +is_tilde_expr(pd, tilde_pos = c(1L, 2L)) + +is_asymmetric_tilde_expr(pd) + +is_symmetric_tilde_expr(pd) } \arguments{ \item{pd}{A parse table.} + +\item{tilde_pos}{Integer vector indicating row-indices that should be +checked for tilde. See 'Details'.} } \description{ -Check whether a parse table corresponds to a certain expression +Check whether a parse table corresponds to a certain expression. +} +\details{ +A tilde is on the top row in the parse table if it is an asymmetric tilde +expression (like \code{~column}), in the second row if it is a symmetric tilde +expression (like \code{a~b}). } \section{Functions}{ \itemize{ -\item \code{is_curly_expr()}: Checks whether \code{pd} contains an expression wrapped in -curly brackets. +\item \code{is_curly_expr()}: Checks whether \code{pd} contains an expression wrapped in curly brackets. -\item \code{is_cond_expr()}: Checks whether \code{pd} contains is a conditional expression. +\item \code{is_for_expr()}: Checks whether \code{pd} contains a \code{for} loop. -\item \code{is_while_expr()}: Checks whether \code{pd} contains is a while loop. +\item \code{is_conditional_expr()}: Checks whether \code{pd} contains is a conditional expression. + +\item \code{is_while_expr()}: Checks whether \code{pd} contains a \code{while} loop. \item \code{is_function_call()}: Checks whether \code{pd} is a function call. -\item \code{is_function_dec()}: Checks whether \code{pd} is a function declaration. +\item \code{is_function_declaration()}: Checks whether \code{pd} is a function declaration. \item \code{is_comment()}: Checks for every token whether or not it is a comment. +\item \code{is_tilde_expr()}: Checks whether \code{pd} contains a tilde. + +\item \code{is_asymmetric_tilde_expr()}: If \code{pd} contains a tilde, checks whether it is asymmetrical. + +\item \code{is_symmetric_tilde_expr()}: If \code{pd} contains a tilde, checks whether it is symmetrical. + }} +\examples{ +code <- "if (TRUE) { 1 }" +pd <- compute_parse_data_nested(code) +is_curly_expr(pd) +child_of_child <- pd$child[[1]]$child[[5]] +is_curly_expr(child_of_child) + +code <- "for (i in 1:5) print(1:i)" +pd <- compute_parse_data_nested(code) +is_for_expr(pd) +is_for_expr(pd$child[[1]]) + +code <- "if (TRUE) x <- 1 else x <- 0" +pd <- compute_parse_data_nested(code) +is_conditional_expr(pd) +is_conditional_expr(pd$child[[1]]) + +code <- "x <- list(1:3)" +pd <- compute_parse_data_nested(code) +is_function_call(pd) +child_of_child <- pd$child[[1]]$child[[3]] +is_function_call(child_of_child) + +code <- "foo <- function() NULL" +pd <- compute_parse_data_nested(code) +is_function_declaration(pd) +child_of_child <- pd$child[[1]]$child[[3]] +is_function_declaration(child_of_child) + +code <- "x <- 1 # TODO: check value" +pd <- compute_parse_data_nested(code) +is_comment(pd) + +code <- "lm(wt ~ mpg, mtcars)" +pd <- compute_parse_data_nested(code) +is_tilde_expr(pd$child[[1]]$child[[3]]) +is_symmetric_tilde_expr(pd$child[[1]]$child[[3]]) +is_asymmetric_tilde_expr(pd$child[[1]]$child[[3]]) + +} +\seealso{ +Other third-party style guide helpers: +\code{\link{next_non_comment}()}, +\code{\link{scope_normalize}()} +} +\concept{third-party style guide helpers} \keyword{internal} diff --git a/man/scope_normalize.Rd b/man/scope_normalize.Rd index 9753da6b0..bd98878e0 100644 --- a/man/scope_normalize.Rd +++ b/man/scope_normalize.Rd @@ -20,4 +20,13 @@ styling tokens includes styling spaces). If individually. See compare \code{\link[=tidyverse_style]{tidyverse_style()}} for the possible levels and their order. } -\keyword{internal} +\examples{ +scope_normalize(I("tokens")) +scope_normalize(I(c("indention", "tokens"))) +} +\seealso{ +Other third-party style guide helpers: +\code{\link{next_non_comment}()}, +\code{\link{pd_is}} +} +\concept{third-party style guide helpers} diff --git a/man/set_space_between_eq_sub_and_comma.Rd b/man/set_space_between_eq_sub_and_comma.Rd index 752f4595e..f0a8677b0 100644 --- a/man/set_space_between_eq_sub_and_comma.Rd +++ b/man/set_space_between_eq_sub_and_comma.Rd @@ -2,7 +2,7 @@ % Please edit documentation in R/rules-spaces.R \name{set_space_between_eq_sub_and_comma} \alias{set_space_between_eq_sub_and_comma} -\title{Set space between EQ_SUB and "','"} +\title{Set space between \code{EQ_SUB} and \code{"','"}} \usage{ set_space_between_eq_sub_and_comma(pd) } @@ -10,6 +10,6 @@ set_space_between_eq_sub_and_comma(pd) \item{pd}{A parse table.} } \description{ -Set space between EQ_SUB and "','" +Set space between \code{EQ_SUB} and \code{"','"} } \keyword{internal} diff --git a/man/tidyverse_style.Rd b/man/tidyverse_style.Rd index 0dac3a710..2d4fc729f 100644 --- a/man/tidyverse_style.Rd +++ b/man/tidyverse_style.Rd @@ -7,7 +7,7 @@ tidyverse_style( scope = "tokens", strict = TRUE, - indent_by = 2, + indent_by = 2L, start_comments_with_one_space = FALSE, reindention = tidyverse_reindention(), math_token_spacing = tidyverse_math_token_spacing() diff --git a/man/token_is_on_aligned_line.Rd b/man/token_is_on_aligned_line.Rd index 5a88c0732..84d6d03e5 100644 --- a/man/token_is_on_aligned_line.Rd +++ b/man/token_is_on_aligned_line.Rd @@ -40,7 +40,7 @@ withr::with_options( list(styler.cache_name = NULL), # temporarily deactivate cache { transformers <- tidyverse_style() - pd_nested <- styler:::compute_parse_data_nested(c( + pd_nested <- compute_parse_data_nested(c( "call(", " ab = 1L,", " a = 2",