Skip to content

Commit

Permalink
detect functional lambdas in object_usage_linter
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico committed Mar 26, 2023
1 parent 4f12a43 commit f6e3916
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 5 deletions.
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@
`R CMD check`, it defaults to `TRUE` (#941, #1458, @IndrajeetPatil).
+ Handles backticked symbols inside {glue} expressions correctly, e.g. ``glue("{`x`}")`` correctly
determines `x` was used (#1619, @MichaelChirico)
+ Detects problems inside R4.1.0+ lambda functions (`\(...)`) (#1933, @MichaelChirico)

* `spaces_inside_linter()` allows terminal missing keyword arguments (e.g. `alist(arg = )`; #540, @MichaelChirico)

Expand Down
10 changes: 5 additions & 5 deletions R/object_usage_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,12 @@ object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) {
# TODO(#1106): use //[...] to capture assignments in more scopes
xpath_function_assignment <- paste(
# direct assignments
"expr[LEFT_ASSIGN or EQ_ASSIGN]/expr[2][FUNCTION]",
"expr_or_assign_or_help[EQ_ASSIGN]/expr[2][FUNCTION]",
"equal_assign[EQ_ASSIGN]/expr[2][FUNCTION]",
"expr[LEFT_ASSIGN or EQ_ASSIGN]/expr[2][FUNCTION or OP-LAMBDA]",
"expr_or_assign_or_help[EQ_ASSIGN]/expr[2][FUNCTION or OP-LAMBDA]",
"equal_assign[EQ_ASSIGN]/expr[2][FUNCTION or OP-LAMBDA]",
# assign() and setMethod() assignments
"//SYMBOL_FUNCTION_CALL[text() = 'assign']/parent::expr/following-sibling::expr[2][FUNCTION]",
"//SYMBOL_FUNCTION_CALL[text() = 'setMethod']/parent::expr/following-sibling::expr[3][FUNCTION]",
"//SYMBOL_FUNCTION_CALL[text() = 'assign']/parent::expr/following-sibling::expr[2][FUNCTION or OP-LAMBDA]",
"//SYMBOL_FUNCTION_CALL[text() = 'setMethod']/parent::expr/following-sibling::expr[3][FUNCTION or OP-LAMBDA]",
sep = " | "
)

Expand Down
14 changes: 14 additions & 0 deletions tests/testthat/test-object_usage_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -624,3 +624,17 @@ test_that("messages without a quoted name are caught", {
object_usage_linter()
)
})

test_that("functional lambda definitions are also caught", {
skip_if_not_r_version("4.1.0")

expect_lint(
trim_some("
fun <- \\() {
a <- 1
}
"),
rex::rex("local variable", anything, "assigned but may not be used"),
object_usage_linter()
)
})

0 comments on commit f6e3916

Please sign in to comment.