Skip to content

Commit

Permalink
ensure no previous expression as well (#2320)
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico authored Nov 20, 2023
1 parent 8414018 commit e50eb09
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 2 deletions.
4 changes: 3 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,9 @@
### Lint accuracy fixes: removing false positives

* `unreachable_code_linter()` ignores reachable code in inline functions like `function(x) if (x > 2) stop() else x` (#2259, @MEO265).
* `unnecessary_lambda_linter()` ignores extractions with explicit returns like `lapply(l, function(x) foo(x)$bar)` (#2258, @MichaelChirico).
* `unnecessary_lambda_linter()`
+ ignores extractions with explicit returns like `lapply(l, function(x) foo(x)$bar)` (#2258, @MichaelChirico).
+ ignores calls on the RHS of operators like `lapply(l, function(x) "a" %in% names(x))` (#2310, @MichaelChirico).

# lintr 3.1.1

Expand Down
5 changes: 4 additions & 1 deletion R/unnecessary_lambda_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,10 @@ unnecessary_lambda_linter <- function() {
position() = 2
and preceding-sibling::expr/SYMBOL_FUNCTION_CALL
and not(preceding-sibling::*[1][self::EQ_SUB])
and not(parent::expr/following-sibling::*[not(self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACE)])
and not(parent::expr[
preceding-sibling::expr[not(SYMBOL_FUNCTION_CALL)]
or following-sibling::*[not(self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACE)]
])
]/SYMBOL
]
/parent::expr
Expand Down
4 changes: 4 additions & 0 deletions tests/testthat/test-unnecessary_lambda_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,10 @@ test_that("unnecessary_lambda_linter skips allowed usages", {
NULL,
linter
)

# only call is on RHS of operator, #2310
expect_lint("lapply(l, function(x) 'a' %in% names(x))", NULL, linter)
expect_lint("lapply(l, function(x = 1) 'a' %in% names(x))", NULL, linter)
})

test_that("unnecessary_lambda_linter blocks simple disallowed usage", {
Expand Down

0 comments on commit e50eb09

Please sign in to comment.