Skip to content

Commit 1b459fc

Browse files
lint %<>% in assignment_linter (#2020)
* lint %<>% * kill whitespace due to bad mobile UI for conflicts * correct message among several lints * more typos --------- Co-authored-by: AshesITR <[email protected]>
1 parent fed901a commit 1b459fc

File tree

4 files changed

+67
-11
lines changed

4 files changed

+67
-11
lines changed

NEWS.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,10 @@
44

55
* `inner_combine_linter()` no longer throws on length-1 calls to `c()` like `c(exp(2))` or `c(log(3))` (#2017, @MichaelChirico). Such usage is discouraged by `unnecessary_concatenation_linter()`, but `inner_combine_linter()` _per se_ does not apply.
66

7+
## Changes to defaults
8+
9+
* `assignment_linter()` lints the {magrittr} assignment pipe `%<>%` (#2008, @MichaelChirico). This can be deactivated by setting the new argument `allow_pipe_assign` to `TRUE`.
10+
711
# lintr 3.1.0
812

913
## Deprecations & Breaking Changes

R/assignment_linter.R

Lines changed: 26 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
#' If `FALSE`, [`<<-`][base::assignOps] and `->>` are not allowed.
77
#' @param allow_right_assign Logical, default `FALSE`. If `TRUE`, `->` and `->>` are allowed.
88
#' @param allow_trailing Logical, default `TRUE`. If `FALSE` then assignments aren't allowed at end of lines.
9+
#' @param allow_pipe_assign Logical, default `FALSE`. If `TRUE`, magrittr's `%<>%` assignment is allowed.
910
#'
1011
#' @examples
1112
#' # will produce lints
@@ -21,6 +22,11 @@
2122
#' linters = assignment_linter()
2223
#' )
2324
#'
25+
#' lint(
26+
#' text = "x %<>% as.character()",
27+
#' linters = assignment_linter()
28+
#' )
29+
#'
2430
#' # okay
2531
#' lint(
2632
#' text = "x <- mean(x)",
@@ -53,19 +59,29 @@
5359
#' linters = assignment_linter(allow_trailing = FALSE)
5460
#' )
5561
#'
62+
#' lint(
63+
#' text = "x %<>% as.character()",
64+
#' linters = assignment_linter(allow_pipe_assign = TRUE)
65+
#' )
66+
#'
5667
#' @evalRd rd_tags("assignment_linter")
5768
#' @seealso
5869
#' - [linters] for a complete list of linters available in lintr.
5970
#' - <https://style.tidyverse.org/syntax.html#assignment-1>
71+
#' - <https://style.tidyverse.org/pipes.html#assignment-2>
6072
#' @export
61-
assignment_linter <- function(allow_cascading_assign = TRUE, allow_right_assign = FALSE, allow_trailing = TRUE) {
73+
assignment_linter <- function(allow_cascading_assign = TRUE,
74+
allow_right_assign = FALSE,
75+
allow_trailing = TRUE,
76+
allow_pipe_assign = FALSE) {
6277
trailing_assign_xpath <- paste(
6378
collapse = " | ",
6479
c(
6580
paste0("//LEFT_ASSIGN", if (allow_cascading_assign) "" else "[text() = '<-']"),
6681
if (allow_right_assign) paste0("//RIGHT_ASSIGN", if (allow_cascading_assign) "" else "[text() = '->']"),
6782
"//EQ_SUB",
68-
"//EQ_FORMALS"
83+
"//EQ_FORMALS",
84+
if (!allow_pipe_assign) "//SPECIAL[text() = '%<>%']"
6985
),
7086
"[@line1 < following-sibling::expr[1]/@line1]"
7187
)
@@ -79,7 +95,8 @@ assignment_linter <- function(allow_cascading_assign = TRUE, allow_right_assign
7995
# NB: := is not linted because of (1) its common usage in rlang/data.table and
8096
# (2) it's extremely uncommon as a normal assignment operator
8197
if (!allow_cascading_assign) "//LEFT_ASSIGN[text() = '<<-']",
82-
if (!allow_trailing) trailing_assign_xpath
98+
if (!allow_trailing) trailing_assign_xpath,
99+
if (!allow_pipe_assign) "//SPECIAL[text() = '%<>%']"
83100
))
84101

85102
Linter(function(source_expression) {
@@ -95,16 +112,16 @@ assignment_linter <- function(allow_cascading_assign = TRUE, allow_right_assign
95112
}
96113

97114
operator <- xml2::xml_text(bad_expr)
98-
lint_message_fmt <- ifelse(
99-
operator %in% c("<<-", "->>"),
100-
"%s can have hard-to-predict behavior; prefer assigning to a specific environment instead (with assign() or <-).",
101-
"Use <-, not %s, for assignment."
102-
)
115+
lint_message_fmt <- rep("Use <-, not %s, for assignment.", length(operator))
116+
lint_message_fmt[operator %in% c("<<-", "->>")] <-
117+
"%s can have hard-to-predict behavior; prefer assigning to a specific environment instead (with assign() or <-)."
118+
lint_message_fmt[operator == "%<>%"] <-
119+
"Avoid the assignment pipe %s; prefer using <- and %%>%% separately."
103120

104121
if (!allow_trailing) {
105122
bad_trailing_expr <- xml2::xml_find_all(xml, trailing_assign_xpath)
106123
trailing_assignments <- xml2::xml_attrs(bad_expr) %in% xml2::xml_attrs(bad_trailing_expr)
107-
lint_message_fmt[trailing_assignments] <- "Assignment %s should not be trailing at end of line"
124+
lint_message_fmt[trailing_assignments] <- "Assignment %s should not be trailing at the end of a line."
108125
}
109126

110127
lint_message <- sprintf(lint_message_fmt, operator)

man/assignment_linter.Rd

Lines changed: 15 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-assignment_linter.R

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ test_that("arguments handle trailing assignment operators correctly", {
5555

5656
expect_lint(
5757
"foo(bar =\n1)",
58-
rex::rex("= should not be trailing"),
58+
rex::rex("= should not be trailing at the end of a line."),
5959
assignment_linter(allow_trailing = FALSE)
6060
)
6161

@@ -163,3 +163,24 @@ test_that("allow_trailing interacts correctly with comments in braced expression
163163
linter
164164
)
165165
})
166+
167+
test_that("%<>% throws a lint", {
168+
expect_lint("x %<>% sum()", "Avoid the assignment pipe %<>%", assignment_linter())
169+
expect_lint("x %<>% sum()", NULL, assignment_linter(allow_pipe_assign = TRUE))
170+
171+
# interaction with allow_trailing
172+
expect_lint("x %<>%\n sum()", "Assignment %<>% should not be trailing", assignment_linter(allow_trailing = FALSE))
173+
})
174+
175+
test_that("multiple lints throw correct messages", {
176+
expect_lint(
177+
"{ x <<- 1; y ->> 2; z -> 3; x %<>% as.character() }",
178+
list(
179+
list(message = "<<- can have hard-to-predict behavior"),
180+
list(message = "->> can have hard-to-predict behavior"),
181+
list(message = "Use <-, not ->"),
182+
list(message = "Avoid the assignment pipe %<>%")
183+
),
184+
assignment_linter(allow_cascading_assign = FALSE)
185+
)
186+
})

0 commit comments

Comments
 (0)