Skip to content

Commit 739b4b6

Browse files
authored
More robust unreachable_code_linter (#2129)
1 parent 2a94dab commit 739b4b6

File tree

3 files changed

+56
-15
lines changed

3 files changed

+56
-15
lines changed

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@
4141
* `function_argument_linter()` detects usage of `missing()` for the linted argument (#1546, @MichaelChirico). The simplest fix for `function_argument_linter()` lints is typically to set that argument to `NULL` by default, in which case it's usually preferable to update function logic checking `missing()` to check `is.null()` instead.
4242
* `equals_na_linter()` checks for `x %in% NA`, which is a more convoluted form of `is.na(x)` (#2088, @MichaelChirico).
4343
* `commas_linter()` gains an option `allow_trailing` (default `FALSE`) to allow trailing commas while indexing. (#2104, @MEO265)
44+
* `unreachable_code_linter()` finds unreachable code even in the presence of a comment or semicolon after `return()` or `stop()` (#2127, @MEO265).
4445

4546
### New linters
4647

R/unreachable_code_linter.R

Lines changed: 6 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -26,22 +26,15 @@
2626
#' @seealso [linters] for a complete list of linters available in lintr.
2727
#' @export
2828
unreachable_code_linter <- function() {
29-
# NB:
30-
# - * returns all children, including the terminal }, so the position
31-
# is not last(), but last()-1. If there's no }, this linter doesn't apply.
32-
# this is also why we need /* and not /expr -- position() must include all nodes
33-
# - use not(OP-DOLLAR) to prevent matching process$stop(), #1051
34-
# - land on the culprit expression
29+
# NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051
3530
xpath <- "
3631
//FUNCTION
3732
/following-sibling::expr
38-
/*[
39-
self::expr
40-
and expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]
41-
and (position() != last() - 1 or not(following-sibling::OP-RIGHT-BRACE))
42-
and @line2 < following-sibling::*[1]/@line2
43-
]
44-
/following-sibling::*[1]
33+
/expr[expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]]
34+
/following-sibling::*[
35+
not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON)
36+
and (not(self::COMMENT) or @line2 > preceding-sibling::*[1]/@line2)
37+
][1]
4538
"
4639

4740
Linter(function(source_expression) {

tests/testthat/test-unreachable_code_linter.R

Lines changed: 49 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,55 @@ test_that("unreachable_code_linter finds unreachable comments", {
7878
)
7979
})
8080

81+
test_that("unreachable_code_linter finds expressions in the same line", {
82+
msg <- rex::rex("Code and comments coming after a top-level return() or stop()")
83+
linter <- unreachable_code_linter()
84+
85+
lines <- trim_some("
86+
foo <- function(x) {
87+
return(
88+
y^2
89+
); 3 + 1
90+
}
91+
")
92+
expect_lint(lines, msg, linter)
93+
94+
lines <- trim_some("
95+
foo <- function(x) {
96+
return(y^2); 3 + 1
97+
}
98+
")
99+
expect_lint(lines, msg, linter)
100+
101+
lines <- trim_some("
102+
foo <- function(x) {
103+
return(y^2); 3 + 1 # Test
104+
}
105+
")
106+
expect_lint(lines, msg, linter)
107+
})
108+
109+
test_that("unreachable_code_linter finds expressions and comments after comment in return line", {
110+
msg <- rex::rex("Code and comments coming after a top-level return() or stop()")
111+
linter <- unreachable_code_linter()
112+
113+
lines <- trim_some("
114+
foo <- function(x) {
115+
return(y^2) #Test comment
116+
#Test comment 2
117+
}
118+
")
119+
expect_lint(lines, msg, linter)
120+
121+
lines <- trim_some("
122+
foo <- function(x) {
123+
return(y^2) # Test
124+
3 + 1
125+
}
126+
")
127+
expect_lint(lines, msg, linter)
128+
})
129+
81130
test_that("unreachable_code_linter finds a double return", {
82131
lines <- trim_some("
83132
foo <- function(x) {
@@ -178,7 +227,5 @@ test_that("unreachable_code_linter ignores terminal nolint end comments", {
178227
# be followed by return(invisible()) or similar), but could be included to
179228
# catch comments for completeness / robustness as a standalone function.
180229
# Terminal if statements are a bit messy, but would have some payoff.
181-
# TODO(michaelchirico): similarly, return(x); x+1 should also lint, even though
182-
# the styler won't allow this in our current setup.
183230
# TODO(michaelchirico): again similarly, this could also apply to cases without
184231
# explicit returns (where it can only apply to comments)

0 commit comments

Comments
 (0)