Skip to content

Commit

Permalink
Anticipate "no exceptions" case for implicit_assignment_linter() (#…
Browse files Browse the repository at this point in the history
…1823)

Closes #1822
  • Loading branch information
IndrajeetPatil authored Dec 9, 2022
1 parent 7c483e6 commit 4d15996
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 2 deletions.
11 changes: 9 additions & 2 deletions R/implicit_assignment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,9 +45,16 @@ implicit_assignment_linter <- function(except = c(
"expect_output", "expect_silent",
"local", "quo", "quos", "quote", "test_that"
)) {
exceptions <- xp_text_in_table(except)
xpath_exceptions <- glue::glue("
stopifnot(is.character(except))

if (length(except) > 0L) {
exceptions <- xp_text_in_table(except)
xpath_exceptions <- glue::glue("
//SYMBOL_FUNCTION_CALL[ not({exceptions}) ]")
} else {
xpath_exceptions <- "
//SYMBOL_FUNCTION_CALL"
}

assignments <- c(
"LEFT_ASSIGN", # e.g. mean(x <- 1:4)
Expand Down
20 changes: 20 additions & 0 deletions tests/testthat/test-implicit_assignment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,26 @@ test_that("implicit_assignment_linter skips allowed usages", {
)
})

test_that("implicit_assignment_linter respects except argument", {
expect_lint(
"local({ a <- 1L })",
NULL,
implicit_assignment_linter(except = character(0L))
)

expect_lint(
"local(a <- 1L)",
rex::rex("Avoid implicit assignments in function calls."),
implicit_assignment_linter(except = character(0L))
)

expect_lint(
"local(a <- 1L)",
NULL,
implicit_assignment_linter(except = "local")
)
})

test_that("implicit_assignment_linter makes exceptions for functions that capture side-effects", {
linter <- implicit_assignment_linter()

Expand Down

0 comments on commit 4d15996

Please sign in to comment.