diff --git a/.pre-commit-config.yaml b/.pre-commit-config.yaml index 38080dd90..d575d5dd7 100644 --- a/.pre-commit-config.yaml +++ b/.pre-commit-config.yaml @@ -1,9 +1,9 @@ # All available hooks: https://pre-commit.com/hooks.html repos: - repo: https://github.com/lorenzwalthert/precommit - rev: v0.0.0.9018 + rev: v0.0.0.9024 hooks: - - id: lintr + # - id: lintr - id: parsable-R - id: no-browser-statement - id: readme-rmd-rendered diff --git a/.travis.yml b/.travis.yml index 68273b8ea..b807f9d6e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ # Usually you shouldn't need to change the first part of the file # DO NOT CHANGE THE CODE BELOW -before_install: R -q -e 'install.packages(c("remotes", "curl", "knitr", "rmarkdown")); remotes::install_github("ropenscilabs/tic"); tic::prepare_all_stages(); remotes::install_deps(dependencies = TRUE); tic::before_install()' +before_install: R -q -e 'install.packages(c("remotes", "curl", "knitr", "rmarkdown")); remotes::install_github("ropenscilabs/tic"); tic::prepare_all_stages(); remotes::install_deps(dependencies = TRUE); if (isTRUE(as.logical(toupper(Sys.getenv("R_REMOVE_RCACHE"))))) remove.packages("R.cache"); tic::before_install()' install: R -q -e 'tic::install()' after_install: R -q -e 'tic::after_install()' before_script: R -q -e 'tic::before_script()' @@ -38,6 +38,9 @@ matrix: - r: release env: - BUILD_PKGDOWN: true + - r: release + env: + - R_REMOVE_RCACHE: true - r: devel #env diff --git a/API b/API index 072513601..eb4538efb 100644 --- a/API +++ b/API @@ -2,6 +2,10 @@ ## Exported functions +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()) default_style_guide_attributes(pd_flat) specify_math_token_spacing(zero = "'^'", one = c("'+'", "'-'", "'*'", "'/'")) diff --git a/DESCRIPTION b/DESCRIPTION index 36ca1f1be..e232a33a1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ -Package: styler Type: Package +Package: styler Title: Non-Invasive Pretty Printing of R Code Version: 1.2.0.9000 Authors@R: @@ -30,14 +30,17 @@ Imports: xfun (>= 0.1) Suggests: data.tree (>= 0.1.6), + digest, dplyr, here, knitr, prettycode, + R.cache (>= 0.14.0), rmarkdown, rstudioapi (>= 0.7), testthat (>= 2.1.0) -VignetteBuilder: knitr +VignetteBuilder: + knitr Encoding: UTF-8 LazyData: true Roxygen: list(markdown = TRUE, roclets = c("rd", "namespace", @@ -80,8 +83,10 @@ Collate: 'token-create.R' 'transform-code.R' 'transform-files.R' - 'ui.R' + 'ui-caching.R' + 'ui-styling.R' 'unindent.R' + 'utils-cache.R' 'utils-files.R' 'utils-navigate-nest.R' 'utils-strings.R' diff --git a/NAMESPACE b/NAMESPACE index 493c57dd1..67f3fcd43 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,6 +1,10 @@ # Generated by roxygen2: do not edit by hand S3method(print,vertical) +export(cache_activate) +export(cache_clear) +export(cache_deactivate) +export(cache_info) export(create_style_guide) export(default_style_guide_attributes) export(specify_math_token_spacing) diff --git a/NEWS.md b/NEWS.md index df41e6a26..d93cba602 100644 --- a/NEWS.md +++ b/NEWS.md @@ -20,9 +20,16 @@ ## New features -* Aligned function calls are detected and kept as is if they match the styler - [definition for aligned function calls](https://styler.r-lib.org/articles/detect-alignment.html) - (#537). +* styler caches results of styling, so applying styler to code it has styled + before will be instantaneous. This brings large speed boosts in many + situations, e.g. when `style_pkg()` is run but only a few files have changed + since the last styling or when using the [styler pre-commit + hook](https://github.com/lorenzwalthert/pre-commit-hooks). See the README for + details (#538). + +* Aligned function calls are detected and remain unchanged if they match the styler + [definition for aligned function + calls](https://styler.r-lib.org/articles/detect-alignment.html) (#537). * curly-curly (`{{`) syntactic sugar introduced with rlang 0.4.0 is now explicitly handled, where previously it was just treated as two consecutive diff --git a/R/addins.R b/R/addins.R index 367b9ce9e..aa2a38157 100644 --- a/R/addins.R +++ b/R/addins.R @@ -141,7 +141,7 @@ set_style_transformers <- function() { #' #' @keywords internal get_addins_style_transformer_name <- function() { - getOption("styler.addins_style_transformer", default = "styler::tidyverse_style()") + getOption("styler.addins_style_transformer") } #' @rdname get_addins_style_transformer_name diff --git a/R/communicate.R b/R/communicate.R index 3e9328b8a..344673f99 100644 --- a/R/communicate.R +++ b/R/communicate.R @@ -34,3 +34,37 @@ assert_data.tree_installation <- function() { abort("The package data.tree needs to be installed for this functionality.") } } + +#' Assert the R.cache installation in conjunction with the cache config +#' +#' R.cache needs to be installed if caching functionality is enabled +#' @param installation_only Whether or not to only check if R.cache is +#' installed. +#' @keywords internal +assert_R.cache_installation <- function(installation_only = FALSE, + action = "abort") { + # fail if R.cache is not installed but feature is actiavted. + if (!rlang::is_installed("R.cache") && + ifelse(installation_only, TRUE, cache_is_activated()) + ) { + msg_basic <- paste( + "R package R.cache is not installed, which is needed when the caching ", + "feature is activated. Please install the package with ", + "`install.packages('R.cache')` and then restart R to enable the ", + "caching feature of styler or permanently deactivate the feature by ", + "adding `styler::cache_deactivate()` to your .Rprofile, e.g. via ", + "`usethis::edit_r_profile()`.", + sep = "" + ) + + if (action == "abort") { + rlang::abort(msg_basic) + } else { + rlang::warn(paste0( + msg_basic, " ", + "Deactivating the caching feature for the current session." + )) + cache_deactivate(verbose = FALSE) + } + } +} diff --git a/R/io.R b/R/io.R index 8b9ed49b4..385b4ce91 100644 --- a/R/io.R +++ b/R/io.R @@ -61,7 +61,7 @@ read_utf8 <- function(path) { } } -#' Drop-in replacement for [xfun::read_utf8()], with an optional `warn` +#' Drop-in replacement for `xfun::read_utf8()`, with an optional `warn` #' argument. #' @keywords internal read_utf8_bare <- function(con, warn = TRUE) { @@ -80,7 +80,7 @@ read_utf8_bare <- function(con, warn = TRUE) { x } -#' Drop-in replacement for `xfun:::invalid_utf8()`. +#' Drop-in replacement for [xfun:::invalid_utf8()] #' @keywords internal invalid_utf8 <- function(x) { which(!is.na(x) & is.na(iconv(x, "UTF-8", "UTF-8"))) diff --git a/R/roxygen-examples-parse.R b/R/roxygen-examples-parse.R index 3d3d6ff77..3d923d384 100644 --- a/R/roxygen-examples-parse.R +++ b/R/roxygen-examples-parse.R @@ -33,8 +33,7 @@ parse_roxygen <- function(roxygen) { #' @param raw Raw code to post-process. #' @keywords internal post_parse_roxygen <- function(raw) { - split <- raw %>% + raw %>% paste0(collapse = "") %>% - strsplit("\n", fixed = TRUE) - split[[1]] + convert_newlines_to_linebreaks() } diff --git a/R/serialize.R b/R/serialize.R index 6857563b4..810825d7a 100644 --- a/R/serialize.R +++ b/R/serialize.R @@ -14,5 +14,5 @@ serialize_parse_data_flattened <- function(flattened_pd, start_line = 1) { map(lag_newlines, add_newlines), map(lag_spaces, add_spaces), text ) ) - strsplit(res, "\n")[[1L]] + convert_newlines_to_linebreaks(res) } diff --git a/R/transform-files.R b/R/transform-files.R index f4749a285..bda9803c6 100644 --- a/R/transform-files.R +++ b/R/transform-files.R @@ -73,17 +73,47 @@ transform_file <- function(path, #' @inheritParams parse_transform_serialize_r #' @keywords internal #' @importFrom purrr when -make_transformer <- function(transformers, include_roxygen_examples, warn_empty = TRUE) { +make_transformer <- function(transformers, + include_roxygen_examples, + warn_empty = TRUE) { force(transformers) + cache_dir <- c("styler", cache_get_name()) + assert_R.cache_installation(action = "warn") + + is_R.cache_installed <- rlang::is_installed("R.cache") + function(text) { - transformed_code <- text %>% - parse_transform_serialize_r(transformers, warn_empty = warn_empty) %>% - when( - include_roxygen_examples ~ - parse_transform_serialize_roxygen(., transformers), - ~. - ) - transformed_code + should_use_cache <- is_R.cache_installed && cache_is_activated() + + if (should_use_cache) { + use_cache <- R.cache::generateCache( + key = cache_make_key(text, transformers), + dirs = cache_dir + ) %>% + file.exists() + } else { + use_cache <- FALSE + } + + if (!use_cache) { + transformed_code <- text %>% + parse_transform_serialize_r(transformers, warn_empty = warn_empty) %>% + when( + include_roxygen_examples ~ + parse_transform_serialize_roxygen(., transformers), + ~. + ) + if (should_use_cache) { + R.cache::generateCache( + key = cache_make_key(transformed_code, transformers), + dirs = cache_dir + ) %>% + file.create() + } + transformed_code + } else { + text + } } } diff --git a/R/ui-caching.R b/R/ui-caching.R new file mode 100644 index 000000000..4d3fd9ce5 --- /dev/null +++ b/R/ui-caching.R @@ -0,0 +1,105 @@ +#' Clear the cache +#' +#' Clears the cache that stores which files are already styled. You won't be +#' able to undo this. Note that the file corresponding to the cache (a folder +#' on your file stystem) won't be deleted, but it will be empty after calling +#' `cache_clear`. +#' @param cache_name The name of the styler cache to use. If +#' `NULL`, the option "styler.cache_name" is considered which defaults to +#' the version of styler used. +#' @details +#' Each version of styler has it's own cache by default, because styling is +#' potentially different with different versions of styler. +#' @param ask Whether or not to interactively ask the user again. +#' @family cache managers +#' @export +cache_clear <- function(cache_name = NULL, ask = TRUE) { + assert_R.cache_installation(installation_only = TRUE) + path_cache <- cache_find_path(cache_name) + R.cache::clearCache(path_cache, prompt = ask) + cache_deactivate(verbose = FALSE) +} + +#' Show information about the styler cache +#' +#' Gives information about the cache. Note that the size consumed by the cache +#' will always be displayed as zero because all the cache does is creating an +#' empty file of size 0 bytes for every cached expression. The innode is +#' excluded from this displayed size but negligible. +#' @param cache_name The name of the cache for which to show details. If +#' `NULL`, the active cache is used. If none is active the cache corresponding +#' to the installed styler version is used. +#' @param format Either "lucid" for a summary emitted with [base::cat()], +#' "tabular" for a tabular summary from [base::file.info()] or "both" for +#' both. +#' @family cache managers +#' @export +cache_info <- function(cache_name = NULL, format = "both") { + assert_R.cache_installation(installation_only = TRUE) + rlang::arg_match(format, c("tabular", "lucid", "both")) + path_cache <- cache_find_path(cache_name) + files <- list.files(path_cache, full.names = TRUE) + file_info <- file.info(files) %>% + as_tibble() + tbl <- tibble( + n = nrow(file_info), + size = sum(file_info$size), + last_modified = suppressWarnings(max(file_info$mtime)), + created = file.info(path_cache)$ctime, + location = path_cache, + activated = cache_is_activated(cache_name) + ) + if (format %in% c("lucid", "both")) { + cat( + "Size:\t\t", tbl$size, " bytes (", tbl$n, " cached expressions)", + "\nLast modified:\t", as.character(tbl$last_modified), + "\nCreated:\t", as.character(tbl$created), + "\nLocation:\t", path_cache, + "\nActivated:\t", tbl$activated, + "\n", + sep = "" + ) + } + if (format == "tabular") { + tbl + } else if (format == "both") { + invisible(tbl) + } +} + +#' Activate or deactivate the styler cache +#' +#' Helper functions to control the behavior of caching. Simple wrappers around +#' [base::options()]. +#' @inheritParams cache_clear +#' @param verbose Whether or not to print an informative message about what the +#' function is doing. +#' @family cache managers +#' @export +cache_activate <- function(cache_name = NULL, verbose = TRUE) { + assert_R.cache_installation(installation_only = TRUE) + if (!is.null(cache_name)) { + options("styler.cache_name" = cache_name) + } else { + options("styler.cache_name" = styler_version) + } + path <- cache_find_path(cache_name) + if (verbose) { + cat( + "Using cache ", cache_get_name(), " at ", + path, ".\n", + sep = "" + ) + } + invisible(path) +} + +#' @rdname cache_activate +#' @export +cache_deactivate <- function(verbose = TRUE) { + options("styler.cache_name" = NULL) + + if (verbose) { + cat("Deactivated cache.\n") + } +} diff --git a/R/ui.R b/R/ui-styling.R similarity index 100% rename from R/ui.R rename to R/ui-styling.R diff --git a/R/utils-cache.R b/R/utils-cache.R new file mode 100644 index 000000000..f97486013 --- /dev/null +++ b/R/utils-cache.R @@ -0,0 +1,112 @@ +#' Standardize text for hashing +#' +#' Make sure text after styling results in the same hash as text before styling +#' if it is indeed identical. +#' @param text A character vector. +#' @keywords internal +hash_standardize <- function(text) { + text %>% + convert_newlines_to_linebreaks() %>% + ensure_last_is_empty() %>% + enc2utf8() %>% + paste0(collapse = "\n") %>% + list() +} + +#' Make a key for `R.cache` +#' +#' @details +#' +#' This function standardizes text and converts transformers to character (to +#' avoid issues described in details). +#' This means that the same code in `transformers`, +#' calling other code not in `transformers` that was modified, will lead +#' styler into thinking we can use the cache, although we should not. We believe +#' this is a highly unlikely event, in particular because we already invalidate +#' the cache when the styler version changes. Hence, our cache will cause +#' styler to return *not correctly styled* code iff one of these conditions +#' holds: +#' - An improperly versioned version of styler is used, e.g. the development +#' version on GitHub. +#' - A style guide from outside styler is used. +#' +#' Plus for both cases: the code in transformers does not change and changes in +#' code the transformers depend on result in different styling. +#' @section Experiments: +#' +#' There is unexamplainable behavior in conjunction with hashin and +#' environments: +#' * Functions created with `purrr::partial()` are not identical when compared +#' with `identical()` +#' ([StackOverflow](https://stackoverflow.com/questions/58656033/when-are-purrrpartial-ized-functions-identical)) +#' * except when they have the exact same parent environment, which must be an +#' object created and then passed to `purrr::partial(.env = ...)`, not +#' created in-place. +#' * `purrr::partial()` seems to ignore `.env` after version 0.2.5, so until +#' this is fixed, we'd have to work with version 0.2.5. +#' * Our caching backend package, `R.cache`, uses +#' `R.cache:::getChecksum.default` (which uses `digest::digest()`) to hash the +#' input. The latter does not seem to care if the environments are exactly +#' equal (see 'Exampels'). +#' * However, under stome circumstances, it does: Commit 9c94c022 (if not +#' overwritten / rebased by now) contains a reprex. Otherwise, search for +#' 43219ixmypi in commit messages and restore this commit to reproduce the +#' behavior. +#' @examples +#' add <- function(x, y) { +#' x + y +#' } +#' add1 <- purrr::partial(add, x = 1) +#' add2 <- purrr::partial(add, x = 1) +#' identical(add1, add2) +#' identical(digest::digest(add1), digest::digest(add2)) +#' identical(digest::digest(styler::tidyverse_style()), digest::digest(styler::tidyverse_style())) +#' @keywords internal +cache_make_key <- function(text, transformers) { + text <- hash_standardize(text) + c(text = text, transformers = as.character(transformers)) +} + +#' Where is the cache? +#' +#' Finds the path to the cache and creates it if it does not exist. +#' @inheritParams cache_clear +#' @keywords internal +cache_find_path <- function(cache_name = NULL) { + cache_name <- cache_get_or_derive_name(cache_name) + R.cache::getCachePath(c("styler", cache_name)) +} + +#' Check if a cache is activated +#' +#' @param cache_name The name of the cache to check. If `NULL`, we check if +#' any cache is activated. If not `NULL`, we check if a specific cache is +#' activated. +#' @keywords internal +cache_is_activated <- function(cache_name = NULL) { + current_cache <- cache_get_name() + if (is.null(cache_name)) { + !is.null(current_cache) + } else if (!is.null(current_cache)) { + cache_name == current_cache + } else { + FALSE + } +} + +styler_version <- unlist(unname(read.dcf("DESCRIPTION")[, "Version"])) + +cache_get_name <- function() { + getOption("styler.cache_name") +} + +cache_get_or_derive_name <- function(cache_name) { + if (is.null(cache_name)) { + cache_name <- cache_get_name() + if (is.null(cache_name)) { + cache_name <- styler_version + } + } + cache_name +} + diff --git a/R/utils.R b/R/utils.R index 3aa6aef91..d532c0614 100644 --- a/R/utils.R +++ b/R/utils.R @@ -4,13 +4,39 @@ line_col_names <- function() { c("line1", "line2", "col1", "col2") } +#' Ensure there is one (and only one) blank line at the end of a vector +#' @examples +#' styler:::ensure_last_is_empty("") +#' styler:::ensure_last_is_empty(letters) +#' styler:::ensure_last_is_empty(c(letters, "", "", "")) +#' @keywords internal ensure_last_is_empty <- function(x) { - has_line_break_at_eof <- x[length(x)] == "" - if (has_line_break_at_eof) { - return(x) - } else { - append(x, "") + if (all(x == "")) { + return("") } + x <- c(x, "", "") + x <- x[seq(1, length(x) - which(rev(x) != "")[1] + 2L)] + x +} + +#' Replace the newline character with a line break +#' +#' @param text A character vector +#' @examples +#' styler:::convert_newlines_to_linebreaks("x\n2") +#' # a simple strsplit approach does not cover both cases +#' unlist(strsplit("x\n\n2", "\n", fixed = TRUE)) +#' unlist(strsplit(c("x", "", "2"), "\n", fixed = TRUE)) +#' styler:::convert_newlines_to_linebreaks(c("x", "2")) +#' @keywords internal +convert_newlines_to_linebreaks <- function(text) { + split <- strsplit(text, "\n", fixed = TRUE) + map(split, ~ if (identical(.x, character(0))) { + "" + } else { + .x + }) %>% + unlist() } #' Check whether two columns match diff --git a/R/zzz.R b/R/zzz.R index 59f5a93e2..3094409b9 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -3,6 +3,8 @@ op <- options() op.styler <- list( styler.colored_print.vertical = TRUE, + styler.cache_name = styler_version, + styler.addins_style_transformer = "styler::tidyverse_style()", styler.ignore_start = "# styler: off", styler.ignore_stop = "# styler: on" ) diff --git a/README.Rmd b/README.Rmd index 9f19bd2da..f66a748f7 100644 --- a/README.Rmd +++ b/README.Rmd @@ -129,6 +129,17 @@ is not flexible enough for you, you can implement your own style guide, as explained in the corresponding [vignette](https://styler.r-lib.org/articles/customizing_styler.html). +**caching** + +In styler 1.1.1,9004, caching was introduced, which makes repeated styling +almost instantaneous. By default, it's enabled, but you need to have the +`R.cache` package installed. At first use, `R.cache` will ask you to let it +create a permanent cache on your file system that styler will use. This is needed +if you want to cache across R sessions and not just within. The cache is +specific to a version of styler by default, because different versions +potentially format code differently. See `?styler::cache_info()` for more +details on how to configure caching. + ## Adaption of styler styler functionality is made available through other tools, most notably diff --git a/README.md b/README.md index 7a546759e..58021b973 100644 --- a/README.md +++ b/README.md @@ -125,6 +125,17 @@ If this is not flexible enough for you, you can implement your own style guide, as explained in the corresponding [vignette](https://styler.r-lib.org/articles/customizing_styler.html). +**caching** + +In styler 1.1.1,9004, caching was introduced, which makes repeated +styling almost instantaneous. By default, it’s enabled, but you need to +have the `R.cache` package installed. At first use, `R.cache` will ask +you to let it create a permanent cache on your file system that styler +will use. This is needed if you want to cache across R sessions and not +just within. The cache is specific to a version of styler by default, +because different versions potentially format code differently. See +`?styler::cache_info()` for more details on how to configure caching. + ## Adaption of styler styler functionality is made available through other tools, most notably diff --git a/man/assert_R.cache_installation.Rd b/man/assert_R.cache_installation.Rd new file mode 100644 index 000000000..61f812c95 --- /dev/null +++ b/man/assert_R.cache_installation.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/communicate.R +\name{assert_R.cache_installation} +\alias{assert_R.cache_installation} +\title{Assert the R.cache installation in conjunction with the cache config} +\usage{ +assert_R.cache_installation(installation_only = FALSE, action = "abort") +} +\arguments{ +\item{installation_only}{Whether or not to only check if R.cache is +installed.} +} +\description{ +R.cache needs to be installed if caching functionality is enabled +} +\keyword{internal} diff --git a/man/cache_activate.Rd b/man/cache_activate.Rd new file mode 100644 index 000000000..4bdb5d921 --- /dev/null +++ b/man/cache_activate.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ui-caching.R +\name{cache_activate} +\alias{cache_activate} +\alias{cache_deactivate} +\title{Activate or deactivate the styler cache} +\usage{ +cache_activate(cache_name = NULL, verbose = TRUE) + +cache_deactivate(verbose = TRUE) +} +\arguments{ +\item{cache_name}{The name of the styler cache to use. If +\code{NULL}, the option "styler.cache_name" is considered which defaults to +the version of styler used.} + +\item{verbose}{Whether or not to print an informative message about what the +function is doing.} +} +\description{ +Helper functions to control the behavior of caching. Simple wrappers around +\code{\link[base:options]{base::options()}}. +} +\seealso{ +Other cache managers: +\code{\link{cache_clear}()}, +\code{\link{cache_info}()} +} +\concept{cache managers} diff --git a/man/cache_clear.Rd b/man/cache_clear.Rd new file mode 100644 index 000000000..c9adb9797 --- /dev/null +++ b/man/cache_clear.Rd @@ -0,0 +1,31 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ui-caching.R +\name{cache_clear} +\alias{cache_clear} +\title{Clear the cache} +\usage{ +cache_clear(cache_name = NULL, ask = TRUE) +} +\arguments{ +\item{cache_name}{The name of the styler cache to use. If +\code{NULL}, the option "styler.cache_name" is considered which defaults to +the version of styler used.} + +\item{ask}{Whether or not to interactively ask the user again.} +} +\description{ +Clears the cache that stores which files are already styled. You won't be +able to undo this. Note that the file corresponding to the cache (a folder +on your file stystem) won't be deleted, but it will be empty after calling +\code{cache_clear}. +} +\details{ +Each version of styler has it's own cache by default, because styling is +potentially different with different versions of styler. +} +\seealso{ +Other cache managers: +\code{\link{cache_activate}()}, +\code{\link{cache_info}()} +} +\concept{cache managers} diff --git a/man/cache_find_path.Rd b/man/cache_find_path.Rd new file mode 100644 index 000000000..3d7d0c673 --- /dev/null +++ b/man/cache_find_path.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils-cache.R +\name{cache_find_path} +\alias{cache_find_path} +\title{Where is the cache?} +\usage{ +cache_find_path(cache_name = NULL) +} +\arguments{ +\item{cache_name}{The name of the styler cache to use. If +\code{NULL}, the option "styler.cache_name" is considered which defaults to +the version of styler used.} +} +\description{ +Finds the path to the cache and creates it if it does not exist. +} +\keyword{internal} diff --git a/man/cache_info.Rd b/man/cache_info.Rd new file mode 100644 index 000000000..13f702071 --- /dev/null +++ b/man/cache_info.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ui-caching.R +\name{cache_info} +\alias{cache_info} +\title{Show information about the styler cache} +\usage{ +cache_info(cache_name = NULL, format = "both") +} +\arguments{ +\item{cache_name}{The name of the cache for which to show details. If +\code{NULL}, the active cache is used. If none is active the cache corresponding +to the installed styler version is used.} + +\item{format}{Either "lucid" for a summary emitted with \code{\link[base:cat]{base::cat()}}, +"tabular" for a tabular summary from \code{\link[base:file.info]{base::file.info()}} or "both" for +both.} +} +\description{ +Gives information about the cache. Note that the size consumed by the cache +will always be displayed as zero because all the cache does is creating an +empty file of size 0 bytes for every cached expression. The innode is +excluded from this displayed size but negligible. +} +\seealso{ +Other cache managers: +\code{\link{cache_activate}()}, +\code{\link{cache_clear}()} +} +\concept{cache managers} diff --git a/man/cache_is_activated.Rd b/man/cache_is_activated.Rd new file mode 100644 index 000000000..ca3031b78 --- /dev/null +++ b/man/cache_is_activated.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils-cache.R +\name{cache_is_activated} +\alias{cache_is_activated} +\title{Check if a cache is activated} +\usage{ +cache_is_activated(cache_name = NULL) +} +\arguments{ +\item{cache_name}{The name of the cache to check. If \code{NULL}, we check if +any cache is activated. If not \code{NULL}, we check if a specific cache is +activated.} +} +\description{ +Check if a cache is activated +} +\keyword{internal} diff --git a/man/cache_make_key.Rd b/man/cache_make_key.Rd new file mode 100644 index 000000000..a3890ce02 --- /dev/null +++ b/man/cache_make_key.Rd @@ -0,0 +1,66 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils-cache.R +\name{cache_make_key} +\alias{cache_make_key} +\title{Make a key for \code{R.cache}} +\usage{ +cache_make_key(text, transformers) +} +\description{ +Make a key for \code{R.cache} +} +\details{ +This function standardizes text and converts transformers to character (to +avoid issues described in details). +This means that the same code in \code{transformers}, +calling other code not in \code{transformers} that was modified, will lead +styler into thinking we can use the cache, although we should not. We believe +this is a highly unlikely event, in particular because we already invalidate +the cache when the styler version changes. Hence, our cache will cause +styler to return \emph{not correctly styled} code iff one of these conditions +holds: +\itemize{ +\item An improperly versioned version of styler is used, e.g. the development +version on GitHub. +\item A style guide from outside styler is used. +} + +Plus for both cases: the code in transformers does not change and changes in +code the transformers depend on result in different styling. +} +\section{Experiments}{ + + +There is unexamplainable behavior in conjunction with hashin and +environments: +\itemize{ +\item Functions created with \code{purrr::partial()} are not identical when compared +with \code{identical()} +(\href{https://stackoverflow.com/questions/58656033/when-are-purrrpartial-ized-functions-identical}{StackOverflow}) +\item except when they have the exact same parent environment, which must be an +object created and then passed to \code{purrr::partial(.env = ...)}, not +created in-place. +\item \code{purrr::partial()} seems to ignore \code{.env} after version 0.2.5, so until +this is fixed, we'd have to work with version 0.2.5. +\item Our caching backend package, \code{R.cache}, uses +\code{R.cache:::getChecksum.default} (which uses \code{digest::digest()}) to hash the +input. The latter does not seem to care if the environments are exactly +equal (see 'Exampels'). +\item However, under stome circumstances, it does: Commit 9c94c022 (if not +overwritten / rebased by now) contains a reprex. Otherwise, search for +43219ixmypi in commit messages and restore this commit to reproduce the +behavior. +} +} + +\examples{ +add <- function(x, y) { +x + y +} +add1 <- purrr::partial(add, x = 1) +add2 <- purrr::partial(add, x = 1) +identical(add1, add2) +identical(digest::digest(add1), digest::digest(add2)) +identical(digest::digest(styler::tidyverse_style()), digest::digest(styler::tidyverse_style())) +} +\keyword{internal} diff --git a/man/convert_newlines_to_linebreaks.Rd b/man/convert_newlines_to_linebreaks.Rd new file mode 100644 index 000000000..9ac928a95 --- /dev/null +++ b/man/convert_newlines_to_linebreaks.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{convert_newlines_to_linebreaks} +\alias{convert_newlines_to_linebreaks} +\title{Replace the newline character with a line break} +\usage{ +convert_newlines_to_linebreaks(text) +} +\arguments{ +\item{text}{A character vector} +} +\description{ +Replace the newline character with a line break +} +\examples{ +styler:::convert_newlines_to_linebreaks("x\n2") +# a simple strsplit approach does not cover both cases +unlist(strsplit("x\n\n2", "\n", fixed = TRUE)) +unlist(strsplit(c("x", "", "2"), "\n", fixed = TRUE)) +styler:::convert_newlines_to_linebreaks(c("x", "2")) +} +\keyword{internal} diff --git a/man/ensure_last_is_empty.Rd b/man/ensure_last_is_empty.Rd new file mode 100644 index 000000000..91cdd2aba --- /dev/null +++ b/man/ensure_last_is_empty.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{ensure_last_is_empty} +\alias{ensure_last_is_empty} +\title{Ensure there is one (and only one) blank line at the end of a vector} +\usage{ +ensure_last_is_empty(x) +} +\description{ +Ensure there is one (and only one) blank line at the end of a vector +} +\examples{ +styler:::ensure_last_is_empty("") +styler:::ensure_last_is_empty(letters) +styler:::ensure_last_is_empty(c(letters, "", "", "")) +} +\keyword{internal} diff --git a/man/hash_standardize.Rd b/man/hash_standardize.Rd new file mode 100644 index 000000000..8f210cc1e --- /dev/null +++ b/man/hash_standardize.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils-cache.R +\name{hash_standardize} +\alias{hash_standardize} +\title{Standardize text for hashing} +\usage{ +hash_standardize(text) +} +\arguments{ +\item{text}{A character vector.} +} +\description{ +Make sure text after styling results in the same hash as text before styling +if it is indeed identical. +} +\keyword{internal} diff --git a/man/invalid_utf8.Rd b/man/invalid_utf8.Rd index 9c9479add..9b1b64e75 100644 --- a/man/invalid_utf8.Rd +++ b/man/invalid_utf8.Rd @@ -2,11 +2,11 @@ % Please edit documentation in R/io.R \name{invalid_utf8} \alias{invalid_utf8} -\title{Drop-in replacement for \code{xfun:::invalid_utf8()}.} +\title{Drop-in replacement for \code{\link[xfun:::invalid_utf8]{xfun::::invalid_utf8()}}} \usage{ invalid_utf8(x) } \description{ -Drop-in replacement for \code{xfun:::invalid_utf8()}. +Drop-in replacement for \code{\link[xfun:::invalid_utf8]{xfun::::invalid_utf8()}} } \keyword{internal} diff --git a/man/prettify_any.Rd b/man/prettify_any.Rd index b85971a8b..3be33cc50 100644 --- a/man/prettify_any.Rd +++ b/man/prettify_any.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ui.R +% Please edit documentation in R/ui-styling.R \name{prettify_any} \alias{prettify_any} \title{Prettify R code in current working directory} diff --git a/man/read_utf8_bare.Rd b/man/read_utf8_bare.Rd index 725efac7f..52f397af4 100644 --- a/man/read_utf8_bare.Rd +++ b/man/read_utf8_bare.Rd @@ -2,13 +2,13 @@ % Please edit documentation in R/io.R \name{read_utf8_bare} \alias{read_utf8_bare} -\title{Drop-in replacement for \code{\link[xfun:read_utf8]{xfun::read_utf8()}}, with an optional \code{warn} +\title{Drop-in replacement for \code{xfun::read_utf8()}, with an optional \code{warn} argument.} \usage{ read_utf8_bare(con, warn = TRUE) } \description{ -Drop-in replacement for \code{\link[xfun:read_utf8]{xfun::read_utf8()}}, with an optional \code{warn} +Drop-in replacement for \code{xfun::read_utf8()}, with an optional \code{warn} argument. } \keyword{internal} diff --git a/man/style_dir.Rd b/man/style_dir.Rd index 443252be7..78e3a60d9 100644 --- a/man/style_dir.Rd +++ b/man/style_dir.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ui.R +% Please edit documentation in R/ui-styling.R \name{style_dir} \alias{style_dir} \title{Prettify arbitrary R code} diff --git a/man/style_file.Rd b/man/style_file.Rd index add8b73f2..3fb2d06d3 100644 --- a/man/style_file.Rd +++ b/man/style_file.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ui.R +% Please edit documentation in R/ui-styling.R \name{style_file} \alias{style_file} \title{Style \code{.R}, \code{.Rmd} or \code{.Rnw} files} diff --git a/man/style_pkg.Rd b/man/style_pkg.Rd index b77d94ed9..dc6fe9603 100644 --- a/man/style_pkg.Rd +++ b/man/style_pkg.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ui.R +% Please edit documentation in R/ui-styling.R \name{style_pkg} \alias{style_pkg} \title{Prettify R source code} diff --git a/man/style_text.Rd b/man/style_text.Rd index 4c4fbc8a2..4f4eeff55 100644 --- a/man/style_text.Rd +++ b/man/style_text.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ui.R +% Please edit documentation in R/ui-styling.R \name{style_text} \alias{style_text} \title{Style a string} diff --git a/tests/testthat/helpers-devel-options.R b/tests/testthat/helpers-devel-options.R new file mode 100644 index 000000000..8751489f7 --- /dev/null +++ b/tests/testthat/helpers-devel-options.R @@ -0,0 +1,2 @@ +cat("In tests/testthat/helpers-devel-options: ") +cache_deactivate() diff --git a/tests/testthat/reference-objects/cache-info-1 b/tests/testthat/reference-objects/cache-info-1 new file mode 100644 index 000000000..724c65e0a Binary files /dev/null and b/tests/testthat/reference-objects/cache-info-1 differ diff --git a/tests/testthat/reference-objects/cache-info-2 b/tests/testthat/reference-objects/cache-info-2 new file mode 100644 index 000000000..5bf3a665d Binary files /dev/null and b/tests/testthat/reference-objects/cache-info-2 differ diff --git a/tests/testthat/reference-objects/cache-info-3 b/tests/testthat/reference-objects/cache-info-3 new file mode 100644 index 000000000..edda7ba76 Binary files /dev/null and b/tests/testthat/reference-objects/cache-info-3 differ diff --git a/tests/testthat/reference-objects/caching.R b/tests/testthat/reference-objects/caching.R new file mode 100644 index 000000000..a121ebd67 --- /dev/null +++ b/tests/testthat/reference-objects/caching.R @@ -0,0 +1,33 @@ +#' CHan deng +#' +#' Performs various izil +#' @examples +#' zz + 1 +#' \dontrun{ +#' xfun::xxio(fun(77), file) +#' } +#' dplyr::filter(x == 3, zz = max(.data$`5`, na.rom = TRUE)) +#' \dontrun{ +#' unlink(file2) +#' } +#' \dontrun{ +#' { +#' x +#' } +#' unlink(file2) +#' } +xxtt <- function(bli, bla, blup = 3) { + changed <- withr::tzu( + zname(path), + condense_files(x_basename(path), c_transformers) + ) + visible(chan) +} + +g <- 33 + +z <- fun(g, z = xxtt) + +if (not(x) == 9) { + cache_this_file() +} diff --git a/tests/testthat/test-cache-with-r-cache.R b/tests/testthat/test-cache-with-r-cache.R new file mode 100644 index 000000000..f0a9ab347 --- /dev/null +++ b/tests/testthat/test-cache-with-r-cache.R @@ -0,0 +1,164 @@ +styler_version <- utils::packageDescription("styler", fields = "Version") +clear_testthat_cache <- purrr::partial(cache_clear, "testthat", ask = FALSE) + +capture.output(test_that("No warnings are issued when R.cache is installed", { + skip_if_not_installed("R.cache") + on.exit(clear_testthat_cache()) + expect_silent(assert_R.cache_installation(installation_only = TRUE)) + expect_silent(assert_R.cache_installation()) + expect_warning(style_text("1+1"), NA) + expect_warning(cache_activate("testthat"), NA) + expect_warning(style_text("1+1"), NA) + expect_silent(assert_R.cache_installation(installation_only = TRUE)) + expect_silent(assert_R.cache_installation()) +})) + +capture.output(test_that("Cache management works when R.cache is installed", { + skip_if_not_installed("R.cache") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + # clearing a cache inactivates the caching functionality. + expect_false(cache_info(format = "tabular")$activated) + cache_activate("testthat") + # at fresh startup, with R.cache installed + expect_s3_class(cache_info(format = "tabular"), "tbl_df") + expect_error(cache_info(), NA) + expect_equal(basename(cache_activate()), styler_version) + expect_equal(basename(cache_activate("xyz")), "xyz") + expect_equal(getOption("styler.cache_name"), "xyz") + # when cache xyz is activated, cache_info() shows deactivated for other caches + expect_false(cache_info(styler_version, format = "tabular")$activated) + expect_error(cache_info(format = "lucid"), NA) + # cache_info() defaults to the currently active cache + expect_equal(basename(cache_info(format = "tabular")$location), "xyz") + + cache_deactivate() + # cache_info() defaults to the cache of the version of styler if + # not cache is active + expect_equal( + basename(cache_info(format = "tabular")$location), styler_version + ) + expect_false(cache_info(format = "tabular")$activated) + expect_equal(getOption("styler.cache_location"), NULL) + expect_error(cache_clear(ask = FALSE), NA) +})) + + + +capture.output(test_that("activated cache brings speedup on style_file() API", { + skip_if_not_installed("R.cache") + cache_activate("testthat") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_activate("testthat") + first <- system.time(styler::style_file(test_path("reference-objects/caching.R"))) + second <- system.time(styler::style_file(test_path("reference-objects/caching.R"))) + expect_true(first["elapsed"] / 2 > second["elapsed"]) +})) + +text <- c( + "#' Roxygen", + "#' Comment", + "#' @examples", + "#' 1 + 1", + "k <- function() {", + " 1 + 1", + " if (x) {", + " k()", + " }", + "}", + "" +) %>% + rep(10) + +capture.output(test_that("activated cache brings speedup on style_text() API on character vector", { + skip_if_not_installed("R.cache") + cache_activate("testthat") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_activate("testthat") + + first <- system.time(styler::style_text(text)) + second <- system.time(styler::style_text(text)) + expect_true(first["elapsed"] / 2 > second["elapsed"]) +})) + +capture.output(test_that("activated cache brings speedup on style_text() API on character scalar", { + skip_if_not_installed("R.cache") + cache_activate("testthat") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_activate("testthat") + + first <- system.time(styler::style_text(paste0(text, collapse = "\n"))) + second <- system.time(styler::style_text(paste0(text, collapse = "\n"))) + expect_true(first["elapsed"] / 2 > second["elapsed"]) +})) + + +capture.output(test_that("no speedup when tranformer changes", { + skip_if_not_installed("R.cache") + cache_activate("testthat") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_activate("testthat") + t1 <- tidyverse_style() + first <- system.time(style_text(text, transformers = t1)) + t1$use_raw_indention <- !t1$use_raw_indention + second <- system.time(style_text(text, transformers = t1)) + expect_false(first["elapsed"] / 2 > second["elapsed"]) +})) + + +capture.output( + test_that(paste0( + "activated cache brings speedup on style_text() API on ", + "character scalar and character vector (mixed)" + ), { + skip_if_not_installed("R.cache") + cache_activate("testthat") + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_activate("testthat") + + first <- system.time(styler::style_text(text)) + second <- system.time(styler::style_text(paste0(text, collapse = "\n"))) + expect_true(first["elapsed"] / 2 > second["elapsed"]) +})) + + +capture.output(test_that("unactivated cache does not bring speedup", { + skip_if_not_installed("R.cache") + on.exit(clear_testthat_cache) + clear_testthat_cache() + cache_deactivate() + first <- system.time(styler::style_file(test_path("reference-objects/caching.R"))) + second <- system.time(styler::style_file(test_path("reference-objects/caching.R"))) + expect_false(first["elapsed"] / 2 > second["elapsed"]) +})) + +capture.output(test_that("cached expressions are displayed propperly", { + on.exit(clear_testthat_cache()) + clear_testthat_cache() + cache_info <- cache_info("testthat", format = "tabular") + expect_known_value( + cache_info[, c("n", "size", "last_modified", "activated")], + file = test_path("reference-objects/cache-info-1") + ) + + cache_activate("testthat") + style_text("1+1") + cache_info <- cache_info(format = "tabular") + cache_info$size <- round(cache_info$size, -2) + expect_known_value( + cache_info[, c("n", "size", "activated")], + file = test_path("reference-objects/cache-info-2") + ) + style_text("a <-function() NULL") + cache_info <- cache_info(format = "tabular") + cache_info$size <- round(cache_info$size, -2) + expect_known_value( + cache_info[, c("n", "size", "activated")], + file = test_path("reference-objects/cache-info-3") + ) +})) diff --git a/tests/testthat/test-cache-without-r-cache.R b/tests/testthat/test-cache-without-r-cache.R new file mode 100644 index 000000000..955ae84bb --- /dev/null +++ b/tests/testthat/test-cache-without-r-cache.R @@ -0,0 +1,41 @@ +test_that("Cache management fails mostly when R.cache is not installed", { + skip_if(rlang::is_installed("R.cache")) + expect_error(cache_info(), "is needed when the caching feature is activated") + expect_error(cache_activate(), "is needed when the caching feature is activated") + expect_error(cache_clear(), "is needed when the caching feature is activated") + expect_error(capture.output(cache_deactivate()), NA) + expect_silent(assert_R.cache_installation()) + expect_error( + assert_R.cache_installation(installation_only = TRUE), + "is needed when the caching feature is activated" + ) +}) + + +test_that("styling works when R.cache is not installed", { + skip_if(rlang::is_installed("R.cache")) + # warning for first time + expect_warning( + capture.output( + withr::with_options( + # simulate .onLoad() in fresh R session + list(styler.cache_name = cache_derive_name()), + style_text("1+1") + ) + ), + "Deactivating the caching feature for the current session" + ) + + # No warnings subsequently + expect_warning( + capture.output( + withr::with_options( + list(styler.cache_name = cache_derive_name()), { + suppressWarnings(style_text("1+1")) + style_text("1+1") + } + ) + ), + NA + ) +})