Skip to content

Commit

Permalink
New empty_assignment_linter (#1637)
Browse files Browse the repository at this point in the history
* New empty_assignment_linter

* hanging indent

* cover right assignments as well; test for := too

* Update R/empty_assignment_linter.R

Co-authored-by: Indrajeet Patil <patilindrajeet.science@gmail.com>
  • Loading branch information
MichaelChirico and IndrajeetPatil authored Oct 8, 2022
1 parent bda3739 commit 35f50e6
Show file tree
Hide file tree
Showing 10 changed files with 145 additions and 2 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ Collate:
'declared_functions.R'
'deprecated.R'
'duplicate_argument_linter.R'
'empty_assignment_linter.R'
'equals_na_linter.R'
'exclude.R'
'expect_comparison_linter.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ export(default_settings)
export(default_undesirable_functions)
export(default_undesirable_operators)
export(duplicate_argument_linter)
export(empty_assignment_linter)
export(equals_na_linter)
export(expect_comparison_linter)
export(expect_identical_linter)
Expand Down
2 changes: 2 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,8 @@

* `for_loop_index_linter()` to prevent overwriting local variables in a `for` loop declared like `for (x in x) { ... }` (@MichaelChirico)

* `empty_assignment_linter()` for identifying empty assignments like `x = {}` that are more clearly written as `x = NULL` (@MichaelChirico)

## Notes

* `lint()` continues to support Rmarkdown documents. For users of custom .Rmd engines, e.g.
Expand Down
62 changes: 62 additions & 0 deletions R/empty_assignment_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,62 @@
#' Block assignment of `{}`
#'
#' Assignment of `{}` is the same as assignment of `NULL`; use the latter
#' for clarity. Closely related: [unneeded_concatenation_linter()].
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "x <- {}",
#' linters = empty_assignment_linter()
#' )
#'
#' cat("x = {\n}")
#' lint(
#' text = "x = {\n}",
#' linters = empty_assignment_linter()
#' )
#'
#' # okay
#' lint(
#' text = "x <- { 3 + 4 }",
#' linters = empty_assignment_linter()
#' )
#'
#' lint(
#' text = "x <- NULL",
#' linters = empty_assignment_linter()
#' )
#'
#' @evalRd rd_tags("empty_assignment_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
empty_assignment_linter <- function() {
# for some reason, the parent in the `=` case is <equal_assign>, not <expr>, hence parent::expr
xpath <- "
//OP-LEFT-BRACE[following-sibling::*[1][self::OP-RIGHT-BRACE]]
/parent::expr[
preceding-sibling::LEFT_ASSIGN
or preceding-sibling::EQ_ASSIGN
or following-sibling::RIGHT_ASSIGN
]
/parent::*
"

Linter(function(source_expression) {
if (!is_lint_level(source_expression, "expression")) {
return(list())
}

xml <- source_expression$xml_parsed_content

bad_expr <- xml2::xml_find_all(xml, xpath)

xml_nodes_to_lints(
bad_expr,
source_expression = source_expression,
lint_message =
"Assign NULL explicitly or, whenever possible, allocate the empty object with the right type and size.",
type = "warning"
)
})
}
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ conjunct_test_linter,package_development best_practices readability
consecutive_stopifnot_linter,style readability consistency
cyclocomp_linter,style readability best_practices default configurable
duplicate_argument_linter,correctness common_mistakes configurable
empty_assignment_linter,readability best_practices
equals_na_linter,robustness correctness common_mistakes default
expect_comparison_linter,package_development best_practices
expect_identical_linter,package_development
Expand Down
1 change: 1 addition & 0 deletions man/best_practices_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

43 changes: 43 additions & 0 deletions man/empty_assignment_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 3 additions & 2 deletions man/linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/readability_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

30 changes: 30 additions & 0 deletions tests/testthat/test-empty_assignment_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
test_that("empty_assignment_linter skips valid usage", {
expect_lint("x <- { 3 + 4 }", NULL, empty_assignment_linter())
expect_lint("x <- if (x > 1) { 3 + 4 }", NULL, empty_assignment_linter())

# also triggers assignment_linter
expect_lint("x = { 3 + 4 }", NULL, empty_assignment_linter())
})

test_that("empty_assignment_linter blocks disallowed usages", {
linter <- empty_assignment_linter()
lint_msg <- rex::rex("Assign NULL explicitly or, whenever possible, allocate the empty object")

expect_lint("xrep <- {}", lint_msg, linter)

# assignment with equal works as well, and white space doesn't matter
expect_lint("x = { }", lint_msg, linter)

# ditto right assignments
expect_lint("{} -> x", lint_msg, linter)
expect_lint("{} ->> x", lint_msg, linter)

# ditto data.table-style walrus assignments
expect_lint("x[, col := {}]", lint_msg, linter)

# newlines also don't matter
expect_lint("x <- {\n}", lint_msg, linter)

# LHS of assignment doesn't matter
expect_lint("env$obj <- {}", lint_msg, linter)
})

0 comments on commit 35f50e6

Please sign in to comment.