Skip to content

Commit

Permalink
Allows the use = instead of <-
Browse files Browse the repository at this point in the history
  • Loading branch information
J-Moravec committed Feb 21, 2024
1 parent 901d9ed commit 63f122f
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 3 deletions.
15 changes: 12 additions & 3 deletions R/assignment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
#'
#' Check that `<-` is always used for assignment.
#'
#' @param allow_equal_assignment Logical, default `FALSE`.
#' If `TRUE`, `=` instead of `<-` is used for assignment.
#' @param allow_cascading_assign Logical, default `TRUE`.
#' If `FALSE`, [`<<-`][base::assignOps] and `->>` are not allowed.
#' @param allow_right_assign Logical, default `FALSE`. If `TRUE`, `->` and `->>` are allowed.
Expand Down Expand Up @@ -70,7 +72,9 @@
#' - <https://style.tidyverse.org/syntax.html#assignment-1>
#' - <https://style.tidyverse.org/pipes.html#assignment-2>
#' @export
assignment_linter <- function(allow_cascading_assign = TRUE,
assignment_linter <- function(
allow_equal_assignment = FALSE,

Check warning on line 76 in R/assignment_linter.R

View workflow job for this annotation

GitHub Actions / lint

file=R/assignment_linter.R,line=76,col=30,[indentation_linter] Indentation should be 4 spaces but is 30 spaces.
allow_cascading_assign = TRUE,
allow_right_assign = FALSE,
allow_trailing = TRUE,
allow_pipe_assign = FALSE) {
Expand All @@ -88,7 +92,7 @@ assignment_linter <- function(allow_cascading_assign = TRUE,

xpath <- paste(collapse = " | ", c(
# always block = (NB: the parser differentiates EQ_ASSIGN, EQ_SUB, and EQ_FORMALS)
"//EQ_ASSIGN",
if (allow_equal_assignment) "//LEFT_ASSIGN" else "//EQ_ASSIGN",
# -> and ->> are both 'RIGHT_ASSIGN'
if (!allow_right_assign) "//RIGHT_ASSIGN" else if (!allow_cascading_assign) "//RIGHT_ASSIGN[text() = '->>']",
# <-, :=, and <<- are all 'LEFT_ASSIGN'; check the text if blocking <<-.
Expand All @@ -108,7 +112,12 @@ assignment_linter <- function(allow_cascading_assign = TRUE,
}

operator <- xml_text(bad_expr)
lint_message_fmt <- rep("Use <-, not %s, for assignment.", length(operator))
lint_message_fmt = rep(

Check warning on line 115 in R/assignment_linter.R

View workflow job for this annotation

GitHub Actions / lint

file=R/assignment_linter.R,line=115,col=22,[assignment_linter] Use <-, not =, for assignment.
paste0("Use ",
if (allow_equal_assignment) "=" else "<-",
", not %s, for assignment."),
length(operator)
)
lint_message_fmt[operator %in% c("<<-", "->>")] <-
"Replace %s by assigning to a specific environment (with assign() or <-) to avoid hard-to-predict behavior."
lint_message_fmt[operator == "%<>%"] <-
Expand Down
8 changes: 8 additions & 0 deletions tests/testthat/test-assignment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -192,3 +192,11 @@ test_that("multiple lints throw correct messages", {
assignment_linter(allow_cascading_assign = FALSE)
)
})

test_that("equal = instead of <- can be used for assignment", {
linter <- assignment_linter(allow_equal_assignment = TRUE)
lint_msg <- rex::rex("Use =, not <-, for assignment.")

expect_lint("blah = 1", NULL, linter)
expect_lint("blah <- 1", lint_msg, linter)
})

0 comments on commit 63f122f

Please sign in to comment.