Skip to content

Commit

Permalink
Merge pull request #849 from lorenzwalthert/multiple-markers
Browse files Browse the repository at this point in the history
Also recognize lintr ignore markers
  • Loading branch information
lorenzwalthert authored Dec 16, 2021
2 parents 6023284 + eaf2864 commit 52cef76
Show file tree
Hide file tree
Showing 8 changed files with 70 additions and 23 deletions.
16 changes: 16 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,22 @@
* Remove dependency on {xfun} (#866).
* use pre-commit via GitHub Actions (#872).

* stylerignore markers are now interpreted as regular expressions instead of
comments that must match exactly. This allows to specify multiple markers in
one regular expression for `styler.ignore_start` and `styler.ignore_stop`,
e.g. to use markers for lintr and styler on the same line, you can use
`options(styler.ignore_start = "nolint start|styler: off"`:

```r
# nolint start, styler: off
1 +1
# nolint end
# styler: on
```
As a consequence of this approach, the defaults for `styler.ignore_start` and
`styler.ignore_stop` omit the `#` (#849).


# styler 1.6.2

* clean up cache files older than one week (#842).
Expand Down
14 changes: 6 additions & 8 deletions R/nest.R
Original file line number Diff line number Diff line change
Expand Up @@ -159,22 +159,20 @@ find_pos_id_to_keep <- function(pd) {
#' [detected by styler](https://styler.r-lib.org/articles/detect-alignment.html),
#' making stylerignore redundant. See a few illustrative examples below.
#' @details
#' Styling is on by default when you run styler.
#' Styling is on for all lines by default when you run styler.
#'
#' - To mark the start of a sequence where you want to turn styling off, use
#' `# styler: off`.
#' - To mark the end of this sequence, put `# styler: on` in your code. After
#' that line, styler will again format your code.
#' - To ignore an inline statement (i.e. just one line), place `# styler: off`
#' at the end of the line. Note that inline statements cannot contain other
#' comments apart from the marker, i.e. a line like
#' `1 # comment # styler: off` won't be ignored.
#'
#' at the end of the line.
#' To use something else as start and stop markers, set the R options
#' `styler.ignore_start` and
#' `styler.ignore_stop` using [options()]. If you want these
#' settings to persist over multiple R sessions, consider setting them in your
#' R profile, e.g. with `usethis::edit_rprofile()`.
#' `styler.ignore_stop` using [options()]. For styler version > 1.6.2, the
#' option supports character vectors longer than one and the marker are not
#' exactly matched, but using a regular expression, which means you can have
#' multiple marker on one line, e.g. `# nolint start styler: off`.
#' @name stylerignore
#' @examples
#' # as long as the order of the markers is correct, the lines are ignored.
Expand Down
11 changes: 8 additions & 3 deletions R/stylerignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -48,13 +48,15 @@ env_add_stylerignore <- function(pd_flat) {
#'
#' See examples in [stylerignore]. Note that you should reuse the stylerignore
#' column to compute switch points or similar and not a plain
#' `pd$text == option_read("styler.ignore_start")` because that will fail to
#' `pd$text %in% option_read("styler.ignore_start")` because that will fail to
#' give correct switch points in the case stylerignore sequences are invalid.
#' @param pd_flat A parse table.
#' @keywords internal
add_stylerignore <- function(pd_flat) {
parse_text <- trimws(pd_flat$text)
start_candidate <- parse_text == option_read("styler.ignore_start")
start_candidate <- grepl(
option_read("styler.ignore_start"), parse_text
) & pd_flat$token == "COMMENT"
pd_flat$stylerignore <- rep(FALSE, length(start_candidate))
env_current$any_stylerignore <- any(start_candidate)
if (!env_current$any_stylerignore) {
Expand All @@ -64,7 +66,10 @@ add_stylerignore <- function(pd_flat) {
pd_flat_lat_line1 <- lag(pd_flat$line2, default = 0)
on_same_line <- pd_flat$line1 == pd_flat_lat_line1
cumsum_start <- cumsum(start_candidate & !on_same_line)
cumsum_stop <- cumsum(parse_text == option_read("styler.ignore_stop"))
cumsum_stop <- cumsum(
grepl(option_read("styler.ignore_stop"), parse_text) &
pd_flat$token == "COMMENT"
)
pd_flat$indicator_off <- cumsum_start + cumsum_stop
is_invalid <- cumsum_start - cumsum_stop < 0 | cumsum_start - cumsum_stop > 1
if (any(is_invalid)) {
Expand Down
4 changes: 2 additions & 2 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@
styler.cache_root = NULL,
styler.cache_name = styler_version,
styler.colored_print.vertical = TRUE,
styler.ignore_start = "# styler: off",
styler.ignore_stop = "# styler: on",
styler.ignore_start = "styler: off",
styler.ignore_stop = "styler: on",
styler.quiet = FALSE,
styler.test_dir_writable = TRUE
)
Expand Down
1 change: 1 addition & 0 deletions inst/WORDLIST
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,7 @@ LF
LIBS
lifecycle
Ligges
lintr
linux
lorenz
lorenzwalthert
Expand Down
2 changes: 1 addition & 1 deletion man/add_stylerignore.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

16 changes: 7 additions & 9 deletions man/stylerignore.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

29 changes: 29 additions & 0 deletions tests/testthat/test-stylerignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,35 @@ test_that("works with other markers", {
)
})


test_that("works for multiple markers inline", {
withr::local_options(styler.ignore_start = "# noeq", )
expect_equal(
style_text(c(
"1+1",
"1+1# noeq",
"1+1"
)) %>%
as.character(),
c("1 + 1", "1+1# noeq", "1 + 1")
)
})


test_that("works for multiple markers inline on one line", {
withr::local_options(styler.ignore_start = "nolint start|styler: off")
expect_equal(
style_text(c(
"1+1",
"1+1# nolint start styler: off",
"1+1"
)) %>%
as.character(),
c("1 + 1", "1+1# nolint start styler: off", "1 + 1")
)
})


test_that("works with other markers", {
expect_warning(
withr::with_options(
Expand Down

0 comments on commit 52cef76

Please sign in to comment.