From 63f122f101f66f0235094f286cb5f6d86392e49c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ji=C5=99=C3=AD=20Moravec?= Date: Thu, 22 Feb 2024 09:50:18 +1300 Subject: [PATCH] Allows the use = instead of <- --- R/assignment_linter.R | 15 ++++++++++++--- tests/testthat/test-assignment_linter.R | 8 ++++++++ 2 files changed, 20 insertions(+), 3 deletions(-) diff --git a/R/assignment_linter.R b/R/assignment_linter.R index da42b5119..fe96dff06 100644 --- a/R/assignment_linter.R +++ b/R/assignment_linter.R @@ -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. @@ -70,7 +72,9 @@ #' - #' - #' @export -assignment_linter <- function(allow_cascading_assign = TRUE, +assignment_linter <- function( + allow_equal_assignment = FALSE, + allow_cascading_assign = TRUE, allow_right_assign = FALSE, allow_trailing = TRUE, allow_pipe_assign = FALSE) { @@ -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 <<-. @@ -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( + 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 == "%<>%"] <- diff --git a/tests/testthat/test-assignment_linter.R b/tests/testthat/test-assignment_linter.R index bae8a048e..71d008d06 100644 --- a/tests/testthat/test-assignment_linter.R +++ b/tests/testthat/test-assignment_linter.R @@ -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) +})