From 05baf80aeddb1645844feae9e6cae8a88f05462d Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 14:07:26 -0800 Subject: [PATCH] exclude %<>% from one_call_pipe_linter (#2331) --- NEWS.md | 1 + R/one_call_pipe_linter.R | 9 ++++++++- man/one_call_pipe_linter.Rd | 6 ++++++ tests/testthat/test-one_call_pipe_linter.R | 20 ++++++++------------ 4 files changed, 23 insertions(+), 13 deletions(-) diff --git a/NEWS.md b/NEWS.md index dafdc1942..8688de5a4 100644 --- a/NEWS.md +++ b/NEWS.md @@ -39,6 +39,7 @@ * `nested_pipe_linter()` for discouraging pipes within pipes, e.g. `df1 %>% inner_join(df2 %>% select(a, b))` (part of #884, @MichaelChirico). * `nrow_subset_linter()` for discouraging usage like `nrow(subset(x, conditions))` in favor of something like `with(x, sum(conditions))` which doesn't require a full subset of `x` (part of #884, @MichaelChirico). * `pipe_return_linter()` for discouraging usage of `return()` inside a {magrittr} pipeline (part of #884, @MichaelChirico). +* `one_call_pipe_linter()` for discouraging one-step pipelines like `x |> as.character()` (#2330 and part of #884, @MichaelChirico). ### Lint accuracy fixes: removing false positives diff --git a/R/one_call_pipe_linter.R b/R/one_call_pipe_linter.R index 4ee4c094d..06bb1a27f 100644 --- a/R/one_call_pipe_linter.R +++ b/R/one_call_pipe_linter.R @@ -31,13 +31,20 @@ #' linters = one_call_pipe_linter() #' ) #' +#' # assignment pipe is exempted +#' lint( +#' text = "DF %<>% mutate(a = 2)", +#' linters = one_call_pipe_linter() +#' ) +#' #' @evalRd rd_tags("one_call_pipe_linter") #' @seealso #' - [linters] for a complete list of linters available in lintr. #' - #' @export one_call_pipe_linter <- function() { - pipes_cond <- xp_text_in_table(magrittr_pipes) + # exception for assignment pipe per #2330 + pipes_cond <- xp_text_in_table(setdiff(magrittr_pipes, "%<>%")) # preceding-sibling::SPECIAL: if there are ever two pipes, don't lint # OP-LEFT-BRACKET/LBB: accept DT[...] %>% .[...] as a two-call pipe, diff --git a/man/one_call_pipe_linter.Rd b/man/one_call_pipe_linter.Rd index a20c19efd..0010826a6 100644 --- a/man/one_call_pipe_linter.Rd +++ b/man/one_call_pipe_linter.Rd @@ -39,6 +39,12 @@ lint( linters = one_call_pipe_linter() ) +# assignment pipe is exempted +lint( + text = "DF \%<>\% mutate(a = 2)", + linters = one_call_pipe_linter() +) + } \seealso{ \itemize{ diff --git a/tests/testthat/test-one_call_pipe_linter.R b/tests/testthat/test-one_call_pipe_linter.R index 50be3a38b..a24f3380b 100644 --- a/tests/testthat/test-one_call_pipe_linter.R +++ b/tests/testthat/test-one_call_pipe_linter.R @@ -7,6 +7,9 @@ test_that("one_call_pipe_linter skips allowed usages", { expect_lint("foo(x) %>% bar()", NULL, linter) # both calls in second step --> OK expect_lint("x %>% foo(bar(.))", NULL, linter) + + # assignment pipe is exempted + expect_lint("x %<>% as.character()", NULL, linter) }) test_that("one_call_pipe_linter blocks simple disallowed usages", { @@ -41,20 +44,13 @@ test_that("one_call_pipe_linter skips data.table chains", { test_that("one_call_pipe_linter treats all pipes equally", { linter <- one_call_pipe_linter() + lint_msg_part <- "Expressions with only a single call shouldn't use pipe " expect_lint("foo %>% bar() %$% col", NULL, linter) + expect_lint("x %T>% foo()", rex::rex(lint_msg_part, "%T>%."), linter) + expect_lint("x %$%\n foo", rex::rex(lint_msg_part, "%$%."), linter) expect_lint( - "x %T>% foo()", - rex::rex("Expressions with only a single call shouldn't use pipe %T>%."), - linter - ) - expect_lint( - "x %$%\n foo()", - rex::rex("Expressions with only a single call shouldn't use pipe %$%."), - linter - ) - expect_lint( - 'data %>% filter(type == "console") %$% obscured_gaia_id %>% unique()', + 'data %>% filter(type == "console") %$% obscured_id %>% unique()', NULL, linter ) @@ -64,7 +60,7 @@ test_that("multiple lints are generated correctly", { expect_lint( trim_some("{ a %>% b() - c %$% d() + c %$% d e %T>% f() }"),