diff --git a/DESCRIPTION b/DESCRIPTION index 0765e5661..c34babb23 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -54,6 +54,7 @@ Collate: 'serialize.R' 'serialized_tests.R' 'style_guides.R' + 'style_rmd.R' 'styler.R' 'token-create.R' 'transform.R' diff --git a/R/style_rmd.R b/R/style_rmd.R new file mode 100644 index 000000000..dd78e5ca1 --- /dev/null +++ b/R/style_rmd.R @@ -0,0 +1,78 @@ +#' Transform code from R or Rmd files +#' +#' A wrapper for [utf8::transform_lines_enc()] which initiates the styling of +#' either R or Rmd files by passing the relevant transformer function for each +#' case. +#' +#' @inheritParams utf8::transform_lines_enc +#' @param ... Further arguments passed to `utf8::transform_lines_enc()`. +transform_code <- function(path, fun, verbose, ...) { + if (grepl("\\.R$", path, ignore.case = TRUE)) { + utf8::transform_lines_enc(path, fun = fun, ...) + } else if (grepl("\\.Rmd$", path, ignore.case = TRUE)) { + utf8::transform_lines_enc(path, fun = partial(transform_rmd, transformer_fun = fun), ...) + } else { + stop(path, " is not an R or Rmd file") + } +} + +#' Transform Rmd contents +#' +#' Applies the supplied transformer function to code chunks identified within +#' an Rmd file and recombines the resulting (styled) code chunks with the text +#' chunks. +#' +#' @param lines A character vector of lines from an Rmd file +#' @param transformer_fun A styler transformer function +#' @importFrom purrr flatten_chr +transform_rmd <- function(lines, transformer_fun) { + chunks <- identify_chunks(lines) + chunks$r_chunks <- map(chunks$r_chunks, transformer_fun) + + map2(chunks$text_chunks, c(chunks$r_chunks, list(character(0))), c) %>% + flatten_chr() +} + + +#' Identify chunks within Rmd contents +#' +#' Identifies the code and text chunks within an Rmd file, and returns these +#' as a nested list. +#' +#' @param lines a character vector of lines from an Rmd file +#' +#' @importFrom purrr map2 +#' @importFrom rlang seq2 +identify_chunks <- function(lines) { + pattern <- get_knitr_pattern(lines) + if (is.null(pattern$chunk.begin) || is.null(pattern$chunk.end)) { + stop("Unrecognized chunk pattern!", call. = FALSE) + } + + starts <- grep(pattern$chunk.begin, lines, perl = TRUE) + ends <- grep(pattern$chunk.end, lines, perl = TRUE) + + if (length(starts) != length(ends)) { + stop("Malformed file!", call. = FALSE) + } + + r_chunks <- map2(starts, ends, ~lines[seq2(.x + 1, .y - 1)]) + + text_chunks <- map2(c(1, ends), c(starts, length(lines)), ~lines[seq2(.x, .y)]) + + lst(r_chunks, text_chunks) +} + +#' Get chunk pattern +#' +#' Determine a regex pattern for identifying R code chunks. +#' +#' @inheritParams identify_chunks +get_knitr_pattern <- function(lines) { + pattern <- knitr:::detect_pattern(lines, "rmd") + if (!is.null(pattern)) { + knitr::all_patterns[[pattern]] + } else { + NULL + } +} diff --git a/R/transform.R b/R/transform.R index 3204f44ec..bbb596de8 100644 --- a/R/transform.R +++ b/R/transform.R @@ -27,9 +27,9 @@ transform_files <- function(files, transformers) { invisible(changed) } -#' Transform a file an give customized message +#' Transform a file and output a customized message #' -#' Wraps `utf8::transform_lines_enc()` and gives customized messages. +#' Wraps `utf8::transform_lines_enc()` and outputs customized messages. #' @param max_char_path The number of characters of the longest path. Determines #' the indention level of `message_after`. #' @param message_before The message to print before the path. @@ -51,7 +51,7 @@ transform_file <- function(path, n_spaces_before_message_after <- max_char_after_message_path - char_after_path message(message_before, path, ".", appendLF = FALSE) - changed <- utf8::transform_lines_enc(path, fun = fun, verbose = verbose, ...) + changed <- transform_code(path, fun = fun, verbose = verbose, ...) message( rep(" ", max(0, n_spaces_before_message_after)), diff --git a/R/ws.R b/R/ws.R index 9b4c786c0..c25a57956 100644 --- a/R/ws.R +++ b/R/ws.R @@ -145,16 +145,6 @@ style_file <- function(path, transformers = style(...)) { withr::with_dir( dirname(path), - prettify_one(transformers, basename(path)) + transform_files(basename(path), transformers) ) } - -#' Prettify one R file -#' -#' This is a helper function for style_dir. -#' @inheritParams style_dir -#' @param path The path to a file that should be styled. -prettify_one <- function(transformers, path) { - if (!grepl("\\.[Rr]$", path)) stop(path, " is not a .R file") - transform_files(path, transformers) -} diff --git a/man/get_knitr_pattern.Rd b/man/get_knitr_pattern.Rd new file mode 100644 index 000000000..042f04753 --- /dev/null +++ b/man/get_knitr_pattern.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/style_rmd.R +\name{get_knitr_pattern} +\alias{get_knitr_pattern} +\title{Get chunk pattern} +\usage{ +get_knitr_pattern(lines) +} +\arguments{ +\item{lines}{a character vector of lines from an Rmd file} +} +\description{ +Determine a regex pattern for identifying R code chunks. +} diff --git a/man/identify_chunks.Rd b/man/identify_chunks.Rd new file mode 100644 index 000000000..daf52ed70 --- /dev/null +++ b/man/identify_chunks.Rd @@ -0,0 +1,15 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/style_rmd.R +\name{identify_chunks} +\alias{identify_chunks} +\title{Identify chunks within Rmd contents} +\usage{ +identify_chunks(lines) +} +\arguments{ +\item{lines}{a character vector of lines from an Rmd file} +} +\description{ +Identifies the code and text chunks within an Rmd file, and returns these +as a nested list. +} diff --git a/man/prettify_one.Rd b/man/prettify_one.Rd deleted file mode 100644 index 084b2945d..000000000 --- a/man/prettify_one.Rd +++ /dev/null @@ -1,18 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ws.R -\name{prettify_one} -\alias{prettify_one} -\title{Prettify one R file} -\usage{ -prettify_one(transformers, path) -} -\arguments{ -\item{transformers}{A set of transformer functions. This argument is most -conveniently constructed via the \code{style} argument and \code{...}. See -'Examples'.} - -\item{path}{The path to a file that should be styled.} -} -\description{ -This is a helper function for style_dir. -} diff --git a/man/transform_code.Rd b/man/transform_code.Rd new file mode 100644 index 000000000..a5768de67 --- /dev/null +++ b/man/transform_code.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/style_rmd.R +\name{transform_code} +\alias{transform_code} +\title{Transform code from R or Rmd files} +\usage{ +transform_code(path, fun, verbose, ...) +} +\arguments{ +\item{path}{A vector of file paths.} + +\item{fun}{A function that returns a character vector.} + +\item{verbose}{Should the function show a message with a list of changed +files?} + +\item{...}{Further arguments passed to \code{utf8::transform_lines_enc()}.} +} +\description{ +A wrapper for \code{\link[utf8:transform_lines_enc]{utf8::transform_lines_enc()}} which initiates the styling of +either R or Rmd files by passing the relevant transformer function for each +case. +} diff --git a/man/transform_file.Rd b/man/transform_file.Rd index e617999d0..9ff703eff 100644 --- a/man/transform_file.Rd +++ b/man/transform_file.Rd @@ -2,7 +2,7 @@ % Please edit documentation in R/transform.R \name{transform_file} \alias{transform_file} -\title{Transform a file an give customized message} +\title{Transform a file and output a customized message} \usage{ transform_file(path, fun, verbose = FALSE, max_char_path, message_before = "", message_after = " [DONE]", @@ -29,5 +29,5 @@ any file was transformed.} \item{...}{Further arguments passed to \code{utf8::transform_lines_enc()}.} } \description{ -Wraps \code{utf8::transform_lines_enc()} and gives customized messages. +Wraps \code{utf8::transform_lines_enc()} and outputs customized messages. } diff --git a/man/transform_rmd.Rd b/man/transform_rmd.Rd new file mode 100644 index 000000000..5a89f0edf --- /dev/null +++ b/man/transform_rmd.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/style_rmd.R +\name{transform_rmd} +\alias{transform_rmd} +\title{Transform Rmd contents} +\usage{ +transform_rmd(lines, transformer_fun) +} +\arguments{ +\item{lines}{A character vector of lines from an Rmd file} + +\item{transformer_fun}{A styler transformer function} +} +\description{ +Applies the supplied transformer function to code chunks identified within +an Rmd file and recombines the resulting (styled) code chunks with the text +chunks. +} diff --git a/tests/testthat/public-api/xyzfile_rmd/random.Rmd b/tests/testthat/public-api/xyzfile_rmd/random.Rmd new file mode 100644 index 000000000..c5528fc5e --- /dev/null +++ b/tests/testthat/public-api/xyzfile_rmd/random.Rmd @@ -0,0 +1,18 @@ +Some text +```{r} +# Some R code +f <- function(x) { + x +} +``` +More text +```{r} +# More R code +g <- function(y) { + y +} +``` +Final text +```{r} +1 + 2 +``` diff --git a/tests/testthat/public-api/xyzfile_rmd/random2.Rmd b/tests/testthat/public-api/xyzfile_rmd/random2.Rmd new file mode 100644 index 000000000..f372022ce --- /dev/null +++ b/tests/testthat/public-api/xyzfile_rmd/random2.Rmd @@ -0,0 +1,18 @@ +```{r} +# Start with chunk +``` +Some text before empty chunk +```{r} + +``` +Final text before longer code chunk +This text chunk has multiple lines +```{r} +# random +this(is_a_call(x)) +if (x) { + r() + a <- 3 + bcds <- 5 +} +``` diff --git a/tests/testthat/public-api/xyzfile_rmd/random3.Rmd b/tests/testthat/public-api/xyzfile_rmd/random3.Rmd new file mode 100644 index 000000000..5ea72f5f4 --- /dev/null +++ b/tests/testthat/public-api/xyzfile_rmd/random3.Rmd @@ -0,0 +1,17 @@ +Some text +```{r} +# Some R code +f <- function(x) { + x +} +``` +More text before malformed chunk +# More R code +g <- function(y) { + y +} +``` +Final text +```{r} +1 + 2 +``` diff --git a/tests/testthat/public-api/xyzfile_rmd/random4.Rmd b/tests/testthat/public-api/xyzfile_rmd/random4.Rmd new file mode 100644 index 000000000..b898ad3b5 --- /dev/null +++ b/tests/testthat/public-api/xyzfile_rmd/random4.Rmd @@ -0,0 +1,17 @@ +Some text +```{r} +# Some R code +f <- function(x) { + x +} +``` +More text +```{r} +# More R code which is invalid +g <- function(y) { + y +``` +Final text +```{r} +1 + 2 +``` diff --git a/tests/testthat/test-public_api.R b/tests/testthat/test-public_api.R index d0ff2c653..df0cc44fb 100644 --- a/tests/testthat/test-public_api.R +++ b/tests/testthat/test-public_api.R @@ -27,3 +27,23 @@ test_that("styler does not return error when there is no file to style", { # styling active region cannot be tested automatically since # rstudioapi::insertText() needs the context id. + +context("public API - Rmd") + +test_that("styler can style Rmd file", { + expect_false( + style_file(testthat_file("public-api", "xyzfile_rmd", "random.Rmd"), strict = FALSE) + ) + expect_false( + style_file(testthat_file("public-api", "xyzfile_rmd", "random2.Rmd"), strict = FALSE) + ) +}) + +test_that("styler handles malformed Rmd file and invalid R code in chunk", { + expect_warning( + style_file(testthat_file("public-api", "xyzfile_rmd", "random3.Rmd"), strict = FALSE) + ) + expect_warning( + style_file(testthat_file("public-api", "xyzfile_rmd", "random4.Rmd"), strict = FALSE) + ) +})