Skip to content

Commit 1493c5e

Browse files
need relative, not global descendant (#2250)
1 parent a6e20bb commit 1493c5e

File tree

2 files changed

+11
-1
lines changed

2 files changed

+11
-1
lines changed

R/unnecessary_lambda_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ unnecessary_lambda_linter <- function() {
7272
count(.//SYMBOL[self::* = preceding::SYMBOL_FORMALS[1]]) = 1
7373
and count(.//SYMBOL_FUNCTION_CALL[text() != 'return']) = 1
7474
and preceding-sibling::SYMBOL_FORMALS =
75-
//expr[
75+
.//expr[
7676
position() = 2
7777
and preceding-sibling::expr/SYMBOL_FUNCTION_CALL
7878
and not(preceding-sibling::*[1][self::EQ_SUB])

tests/testthat/test-unnecessary_lambda_linter.R

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,16 @@ test_that("unnecessary_lambda_linter skips allowed usages", {
5555
expect_lint("lapply(l, function(x) foo(x) * 2)", NULL, linter)
5656
expect_lint("lapply(l, function(x) foo(x) ^ 3)", NULL, linter)
5757
expect_lint("lapply(l, function(x) foo(x) %% 4)", NULL, linter)
58+
59+
# Don't include other lambdas, #2249
60+
expect_lint(
61+
trim_some('{
62+
lapply(x, function(e) sprintf("%o", e))
63+
lapply(y, function(e) paste(strlpad(e, "0", width)))
64+
}'),
65+
NULL,
66+
linter
67+
)
5868
})
5969

6070
test_that("unnecessary_lambda_linter blocks simple disallowed usage", {

0 commit comments

Comments
 (0)