Skip to content

Commit

Permalink
Fix false positive 'unreachables' (#2262)
Browse files Browse the repository at this point in the history
* Add new tests and remove false negative

* mnt: Space after `if` in tests

* mnt: Update NEWS

* Clarify NEWS

---------

Co-authored-by: Michael Chirico <[email protected]>
  • Loading branch information
MEO265 and MichaelChirico committed Mar 21, 2024
1 parent 49107a6 commit 8c1522c
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 1 deletion.
5 changes: 5 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,11 @@

* Fixed a test assuming a specific parser error message that recently changed in r-devel (#2527, @IndrajeetPatil).

## New and improved features

### 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).

# lintr 3.1.1

## Breaking changes
Expand Down
2 changes: 1 addition & 1 deletion R/unreachable_code_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ unreachable_code_linter <- function() {
xpath_return_stop <- glue("
(
{expr_after_control}
| (//FUNCTION | //OP-LAMBDA)/following-sibling::expr
| (//FUNCTION | //OP-LAMBDA)[following-sibling::expr[1]/*[1][self::OP-LEFT-BRACE]]/following-sibling::expr[1]
)
/expr[expr[1][
not(OP-DOLLAR or OP-AT)
Expand Down
44 changes: 44 additions & 0 deletions tests/testthat/test-unreachable_code_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -597,6 +597,50 @@ test_that("function shorthand is handled", {
)
})

test_that("Do not lint inline else after stop", {

expect_lint(
"if (x > 3L) stop() else x + 3",
NULL,
unreachable_code_linter()
)
})

test_that("Do not lint inline else after stop in inline function", {

expect_lint(
"function(x) if (x > 3L) stop() else x + 3",
NULL,
unreachable_code_linter()
)

expect_lint(
"function(x) if (x > 3L) { stop() } else {x + 3}",
NULL,
unreachable_code_linter()
)
})

test_that("Do not lint inline else after stop in inline lambda function", {
skip_if_not_r_version("4.1.0")

expect_lint(
"\\(x) if (x > 3L) stop() else x + 3",
NULL,
unreachable_code_linter()
)
})

test_that("Do not lint inline else after stop in lambda function", {
skip_if_not_r_version("4.1.0")

expect_lint(
"\\(x){ if (x > 3L) stop() else x + 3 }",
NULL,
unreachable_code_linter()
)
})

# nolint start: commented_code_linter.
# TODO(michaelchirico): extend to work on switch() statements
# test_that("unreachable_code_linter interacts with switch() as expected", {
Expand Down

0 comments on commit 8c1522c

Please sign in to comment.