From 5872b25f00db7fa5daa42cc976e924bc39a06034 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Sun, 10 Sep 2023 17:49:09 +0200 Subject: [PATCH 01/22] Lint unreachable code in loops --- R/unreachable_code_linter.R | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index ac2f2cb89..89047e889 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -57,8 +57,7 @@ unreachable_code_linter <- function() { # NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051 xpath_return_stop <- " - //FUNCTION - /following-sibling::expr + ((//FUNCTION | //REPEAT)/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) /expr[expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]] /following-sibling::*[ not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) From aeca511330d3c3d8e79df5c5fd52cf57bd622cdb Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 18:27:28 +0200 Subject: [PATCH 02/22] Add tests --- tests/testthat/test-unreachable_code_linter.R | 73 +++++++++++++++++++ 1 file changed, 73 insertions(+) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index 6dce10e4d..71699a75b 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -7,6 +7,79 @@ test_that("unreachable_code_linter works in simple function", { expect_lint(lines, NULL, unreachable_code_linter()) }) +test_that("unreachable_code_linter works in sub expressions", { + linter <- unreachable_code_linter() + msg <- rex::rex("Code and comments coming after a top-level return() or stop()") + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + return(bar) + # Test comment + while (bar) { + return(bar) + 5 + 3 + repeat { + return(bar) + # Test comment + } + } + } + return(bar) + 5 + 1 + } + ") + + expect_lint( + lines, + list( + list(line_number = 4L, message = msg), + list(line_number = 7L, message = msg), + list(line_number = 10L, message = msg), + list(line_number = 15L, message = msg) + ), + linter) + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + return(bar) # Test comment + } + while (bar) { + return(bar) # 5 + 3 + } + repeat { + return(bar) # Test comment + } + } + ") + + expect_lint(lines, NULL, linter) + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + return(bar); x <- 2 + } + while (bar) { + return(bar); 5 + 3 + } + repeat { + return(bar); test() + } + } + ") + + expect_lint( + lines, + list( + list(line_number = 3L, message = msg), + list(line_number = 6L, message = msg), + list(line_number = 9L, message = msg) + ), + linter) +}) + test_that("unreachable_code_linter ignores expressions that aren't functions", { expect_lint("x + 1", NULL, unreachable_code_linter()) }) From 82a22ba41143b1dd823f29bf5abfdd638ae4dcff Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 18:28:10 +0200 Subject: [PATCH 03/22] Update doc --- R/unreachable_code_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index 89047e889..6a546d93e 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -1,6 +1,6 @@ #' Block unreachable code and comments following return statements #' -#' Code after a top-level [return()] or [stop()] +#' Code after a [return()] or [stop()] #' or in deterministically false conditional loops like `if (FALSE)` can't be reached; #' typically this is vestigial code left after refactoring or sandboxing code, which #' is fine for exploration, but shouldn't ultimately be checked in. Comments From db3869f89e386da8161de3b6838ec4484942b9c8 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 18:30:32 +0200 Subject: [PATCH 04/22] Update lint warning message --- R/unreachable_code_linter.R | 2 +- tests/testthat/test-unreachable_code_linter.R | 18 +++++++++--------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index 6a546d93e..2a0c76bb1 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -103,7 +103,7 @@ unreachable_code_linter <- function() { lints_return_stop <- xml_nodes_to_lints( expr_return_stop[!is_nolint_end_comment], source_expression = source_expression, - lint_message = "Code and comments coming after a top-level return() or stop() should be removed.", + lint_message = "Code and comments coming after a return() or stop() should be removed.", type = "warning" ) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index 71699a75b..ed3057e16 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -9,7 +9,7 @@ test_that("unreachable_code_linter works in simple function", { test_that("unreachable_code_linter works in sub expressions", { linter <- unreachable_code_linter() - msg <- rex::rex("Code and comments coming after a top-level return() or stop()") + msg <- rex::rex("Code and comments coming after a return() or stop()") lines <- trim_some(" foo <- function(bar) { @@ -130,7 +130,7 @@ test_that("unreachable_code_linter identifies simple unreachable code", { lines, list( line_number = 3L, - message = rex::rex("Code and comments coming after a top-level return() or stop()") + message = rex::rex("Code and comments coming after a return() or stop()") ), unreachable_code_linter() ) @@ -146,13 +146,13 @@ test_that("unreachable_code_linter finds unreachable comments", { ") expect_lint( lines, - rex::rex("Code and comments coming after a top-level return() or stop()"), + rex::rex("Code and comments coming after a return() or stop()"), unreachable_code_linter() ) }) test_that("unreachable_code_linter finds expressions in the same line", { - msg <- rex::rex("Code and comments coming after a top-level return() or stop()") + msg <- rex::rex("Code and comments coming after a return() or stop()") linter <- unreachable_code_linter() lines <- trim_some(" @@ -180,7 +180,7 @@ test_that("unreachable_code_linter finds expressions in the same line", { }) test_that("unreachable_code_linter finds expressions and comments after comment in return line", { - msg <- rex::rex("Code and comments coming after a top-level return() or stop()") + msg <- rex::rex("Code and comments coming after a return() or stop()") linter <- unreachable_code_linter() lines <- trim_some(" @@ -209,7 +209,7 @@ test_that("unreachable_code_linter finds a double return", { ") expect_lint( lines, - rex::rex("Code and comments coming after a top-level return() or stop()"), + rex::rex("Code and comments coming after a return() or stop()"), unreachable_code_linter() ) }) @@ -224,7 +224,7 @@ test_that("unreachable_code_linter finds code after stop()", { ") expect_lint( lines, - rex::rex("Code and comments coming after a top-level return() or stop()"), + rex::rex("Code and comments coming after a return() or stop()"), unreachable_code_linter() ) }) @@ -422,7 +422,7 @@ test_that("unreachable_code_linter identifies unreachable code in mixed conditio ), list( line_number = 13L, - message = rex::rex("Code and comments coming after a top-level return() or stop()") + message = rex::rex("Code and comments coming after a return() or stop()") ) ), linter @@ -462,7 +462,7 @@ test_that("unreachable_code_linter identifies unreachable code in mixed conditio # ") # expect_lint( # unreachable_inside_switch_lines, -# rex::rex("Code and comments coming after a top-level return() or stop()"), +# rex::rex("Code and comments coming after a return() or stop()"), # unreachable_code_linter() # ) # }) From 7483afb1d74485aeca73811b2b78692b24b68f39 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:04:03 +0200 Subject: [PATCH 05/22] Lint next and break --- R/unreachable_code_linter.R | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index 2a0c76bb1..4b05893e9 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -64,6 +64,15 @@ unreachable_code_linter <- function() { and (not(self::COMMENT) or @line2 > preceding-sibling::*[1]/@line2) ][1] " + xpath_next_break <- " + (//REPEAT/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) + /expr[NEXT or BREAK] + /following-sibling::*[ + not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) + and (not(self::COMMENT) or @line2 > preceding-sibling::*[1]/@line2) + ][1] + " + xpath_if_while <- " (//WHILE | //IF)[following-sibling::expr[1]/NUM_CONST[text() = 'FALSE']]/following-sibling::expr[2] " @@ -107,6 +116,15 @@ unreachable_code_linter <- function() { type = "warning" ) + expr_next_break <- xml_find_all(xml, xpath_next_break) + + lints_next_break <- xml_nodes_to_lints( + expr_next_break, + source_expression = source_expression, + lint_message = "Code and comments coming after a `next` or `break` should be removed.", + type = "warning" + ) + expr_if_while <- handle_inline_conditions(xml_find_all(xml, xpath_if_while)) lints_if_while <- xml_nodes_to_lints( @@ -125,6 +143,6 @@ unreachable_code_linter <- function() { type = "warning" ) - c(lints_return_stop, lints_if_while, lints_else) + c(lints_return_stop, lints_next_break, lints_if_while, lints_else) }) } From a816863b0b381e8f3e9b551684f0dddab2a84cc3 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:05:46 +0200 Subject: [PATCH 06/22] Update doc --- R/unreachable_code_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index 4b05893e9..afc17c122 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -1,6 +1,6 @@ #' Block unreachable code and comments following return statements #' -#' Code after a [return()] or [stop()] +#' Code after e.g. a [return()] or [stop()] #' or in deterministically false conditional loops like `if (FALSE)` can't be reached; #' typically this is vestigial code left after refactoring or sandboxing code, which #' is fine for exploration, but shouldn't ultimately be checked in. Comments From 70f05c5ace32cd6f3ca38109224a75dcf3385677 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:06:06 +0200 Subject: [PATCH 07/22] Update man --- man/unreachable_code_linter.Rd | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/man/unreachable_code_linter.Rd b/man/unreachable_code_linter.Rd index 34dabf257..4e91e5cf8 100644 --- a/man/unreachable_code_linter.Rd +++ b/man/unreachable_code_linter.Rd @@ -7,7 +7,7 @@ unreachable_code_linter() } \description{ -Code after a top-level \code{\link[=return]{return()}} or \code{\link[=stop]{stop()}} +Code after e.g. a \code{\link[=return]{return()}} or \code{\link[=stop]{stop()}} or in deterministically false conditional loops like \verb{if (FALSE)} can't be reached; typically this is vestigial code left after refactoring or sandboxing code, which is fine for exploration, but shouldn't ultimately be checked in. Comments From 7e408d5dc0d9b622b0881afa66e0666dc2aa1f08 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:15:53 +0200 Subject: [PATCH 08/22] Add test for next and break --- tests/testthat/test-unreachable_code_linter.R | 70 +++++++++++++++++++ 1 file changed, 70 insertions(+) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index ed3057e16..5a977aaea 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -80,6 +80,76 @@ test_that("unreachable_code_linter works in sub expressions", { linter) }) +test_that("unreachable_code_linter works with next and break in sub expressions", { + linter <- unreachable_code_linter() + msg <- rex::rex("Code and comments coming after a `next` or `break`") + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + next + # Test comment + while (bar) { + break + 5 + 3 + repeat { + next + # Test comment + } + } + } + } + ") + + expect_lint( + lines, + list( + list(line_number = 4L, message = msg), + list(line_number = 7L, message = msg), + list(line_number = 10L, message = msg) + ), + linter) + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + break # Test comment + } + while (bar) { + next # 5 + 3 + } + repeat { + next # Test comment + } + } + ") + + expect_lint(lines, NULL, linter) + + lines <- trim_some(" + foo <- function(bar) { + if (bar) { + next; x <- 2 + } + while (bar) { + break; 5 + 3 + } + repeat { + next; test() + } + } + ") + + expect_lint( + lines, + list( + list(line_number = 3L, message = msg), + list(line_number = 6L, message = msg), + list(line_number = 9L, message = msg) + ), + linter) +}) + test_that("unreachable_code_linter ignores expressions that aren't functions", { expect_lint("x + 1", NULL, unreachable_code_linter()) }) From 3c490c3bf3699056b952d6a5b5003a4aa8127b48 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:17:04 +0200 Subject: [PATCH 09/22] Ignore nolint comments for next and break --- R/unreachable_code_linter.R | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index afc17c122..b0cabc3a5 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -118,8 +118,11 @@ unreachable_code_linter <- function() { expr_next_break <- xml_find_all(xml, xpath_next_break) + is_nolint_end_comment <- xml2::xml_name(expr_next_break) == "COMMENT" & + re_matches(xml_text(expr_next_break), settings$exclude_end) + lints_next_break <- xml_nodes_to_lints( - expr_next_break, + expr_next_break[!is_nolint_end_comment], source_expression = source_expression, lint_message = "Code and comments coming after a `next` or `break` should be removed.", type = "warning" From 2d482e62c43d22c3d861ee5f6402b1f40d486f10 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:25:50 +0200 Subject: [PATCH 10/22] Tests for nolint comments --- tests/testthat/test-unreachable_code_linter.R | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index 5a977aaea..797182c77 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -338,6 +338,20 @@ test_that("unreachable_code_linter ignores terminal nolint end comments", { NULL, list(unreachable_code_linter(), one_linter = assignment_linter()) ) + + expect_lint( + trim_some(" + foo <- function() { + do_something + # nolint start: one_linter. + a = 42 + next + # nolint end + } + "), + NULL, + unreachable_code_linter() + ) }) test_that("unreachable_code_linter identifies unreachable code in conditional loops", { From c577c50b1146c3424f6704bbdb7a3257fcb68645 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Mon, 11 Sep 2023 22:26:33 +0200 Subject: [PATCH 11/22] Indentation fix --- tests/testthat/test-unreachable_code_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index 797182c77..bfc904456 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -339,7 +339,7 @@ test_that("unreachable_code_linter ignores terminal nolint end comments", { list(unreachable_code_linter(), one_linter = assignment_linter()) ) - expect_lint( + expect_lint( trim_some(" foo <- function() { do_something From ea3820b9b7efc0ccbf3fc3d19f6db25dc5e6d484 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Tue, 12 Sep 2023 03:25:44 +0200 Subject: [PATCH 12/22] Consider for and else --- R/unreachable_code_linter.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index b0cabc3a5..25434dec7 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -57,7 +57,7 @@ unreachable_code_linter <- function() { # NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051 xpath_return_stop <- " - ((//FUNCTION | //REPEAT)/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) + ((//FUNCTION | //REPEAT | //ELSE | //FOR)/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) /expr[expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]] /following-sibling::*[ not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) @@ -65,7 +65,7 @@ unreachable_code_linter <- function() { ][1] " xpath_next_break <- " - (//REPEAT/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) + ((//REPEAT | //ELSE | //FOR)/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) /expr[NEXT or BREAK] /following-sibling::*[ not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) From c22d7f0937493b6ae5ccdec8871560297febf1b3 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Tue, 12 Sep 2023 03:32:41 +0200 Subject: [PATCH 13/22] Update NEWS --- NEWS.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 4082dc451..8397206b0 100644 --- a/NEWS.md +++ b/NEWS.md @@ -45,7 +45,8 @@ * `unreachable_code_linter()` + finds unreachable code even in the presence of a comment or semicolon after `return()` or `stop()` (#2127, @MEO265). + checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). - + + checks for unreachable code inside `if`, `else`, `for`, `while`, and `repeat` blocks, including combinations with `break` and `next` statements." (#2105, @ME0265). + ### New linters * `library_call_linter()` can detect if all library/require calls are not at the top of your script (#2027 and #2043, @nicholas-masel and @MichaelChirico). From f825ea9dfc1a3417f8f36f7e443c0bbe6bb8d6a3 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Tue, 12 Sep 2023 04:19:38 +0200 Subject: [PATCH 14/22] Fix linebreak --- tests/testthat/test-unreachable_code_linter.R | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index bfc904456..fa6feb9fe 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -38,7 +38,8 @@ test_that("unreachable_code_linter works in sub expressions", { list(line_number = 10L, message = msg), list(line_number = 15L, message = msg) ), - linter) + linter + ) lines <- trim_some(" foo <- function(bar) { @@ -77,7 +78,8 @@ test_that("unreachable_code_linter works in sub expressions", { list(line_number = 6L, message = msg), list(line_number = 9L, message = msg) ), - linter) + linter + ) }) test_that("unreachable_code_linter works with next and break in sub expressions", { @@ -108,7 +110,8 @@ test_that("unreachable_code_linter works with next and break in sub expressions" list(line_number = 7L, message = msg), list(line_number = 10L, message = msg) ), - linter) + linter + ) lines <- trim_some(" foo <- function(bar) { @@ -147,7 +150,8 @@ test_that("unreachable_code_linter works with next and break in sub expressions" list(line_number = 6L, message = msg), list(line_number = 9L, message = msg) ), - linter) + linter + ) }) test_that("unreachable_code_linter ignores expressions that aren't functions", { From 134dcaa62ad9bea721a615cdbe593c5930e48477 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Tue, 12 Sep 2023 17:15:32 +0200 Subject: [PATCH 15/22] Fix NEWS --- NEWS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 37fd5a119..51d6f4feb 100644 --- a/NEWS.md +++ b/NEWS.md @@ -44,7 +44,7 @@ * `unreachable_code_linter()` + finds unreachable code even in the presence of a comment or semicolon after `return()` or `stop()` (#2127, @MEO265). + checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). - + checks for unreachable code inside `if`, `else`, `for`, `while`, and `repeat` blocks, including combinations with `break` and `next` statements." (#2105, @ME0265). + + checks for unreachable code inside `if`, `else`, `for`, `while`, and `repeat` blocks, including combinations with `break` and `next` statements. (#2105, @ME0265). * `inner_combine_linter()` no longer throws on length-1 calls to `c()` like `c(exp(2))` or `c(log(3))` (#2017, @MichaelChirico). Such usage is discouraged by `unnecessary_concatenation_linter()`, but `inner_combine_linter()` _per se_ does not apply. * `condition_message_linter()` ignores usages of extracted calls like `env$stop(paste(a, b))` (#1455, @MichaelChirico). From cbd135208b00d905edaab25d3d084c8a6970ebcf Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Tue, 12 Sep 2023 17:27:33 +0200 Subject: [PATCH 16/22] Additional tests --- tests/testthat/test-unreachable_code_linter.R | 55 +++++++++++++++++-- 1 file changed, 49 insertions(+), 6 deletions(-) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index fa6feb9fe..1744699b0 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -24,6 +24,17 @@ test_that("unreachable_code_linter works in sub expressions", { # Test comment } } + } else if (bla) { + # test + return(5) + # Test 2 + } else { + return(bar) + # Test comment + for(i in 1:3) { + return(bar) + 5 + 4 + } } return(bar) 5 + 1 @@ -36,7 +47,10 @@ test_that("unreachable_code_linter works in sub expressions", { list(line_number = 4L, message = msg), list(line_number = 7L, message = msg), list(line_number = 10L, message = msg), - list(line_number = 15L, message = msg) + list(line_number = 16L, message = msg), + list(line_number = 19L, message = msg), + list(line_number = 22L, message = msg), + list(line_number = 26L, message = msg) ), linter ) @@ -52,6 +66,7 @@ test_that("unreachable_code_linter works in sub expressions", { repeat { return(bar) # Test comment } + } ") @@ -61,6 +76,8 @@ test_that("unreachable_code_linter works in sub expressions", { foo <- function(bar) { if (bar) { return(bar); x <- 2 + } else { + return(bar); x <- 3 } while (bar) { return(bar); 5 + 3 @@ -68,6 +85,9 @@ test_that("unreachable_code_linter works in sub expressions", { repeat { return(bar); test() } + for(i in 1:3) { + return(bar); 5 + 4 + } } ") @@ -75,8 +95,10 @@ test_that("unreachable_code_linter works in sub expressions", { lines, list( list(line_number = 3L, message = msg), - list(line_number = 6L, message = msg), - list(line_number = 9L, message = msg) + list(line_number = 5L, message = msg), + list(line_number = 8L, message = msg), + list(line_number = 11L, message = msg), + list(line_number = 14L, message = msg) ), linter ) @@ -99,6 +121,13 @@ test_that("unreachable_code_linter works with next and break in sub expressions" # Test comment } } + } else { + next + # test + for(i in 1:3) { + break + 5 + 4 + } } } ") @@ -108,7 +137,9 @@ test_that("unreachable_code_linter works with next and break in sub expressions" list( list(line_number = 4L, message = msg), list(line_number = 7L, message = msg), - list(line_number = 10L, message = msg) + list(line_number = 10L, message = msg), + list(line_number = 15L, message = msg), + list(line_number = 18L, message = msg) ), linter ) @@ -117,6 +148,8 @@ test_that("unreachable_code_linter works with next and break in sub expressions" foo <- function(bar) { if (bar) { break # Test comment + } else { + next # Test comment } while (bar) { next # 5 + 3 @@ -124,6 +157,9 @@ test_that("unreachable_code_linter works with next and break in sub expressions" repeat { next # Test comment } + for(i in 1:3) { + break # 5 + 4 + } } ") @@ -133,6 +169,8 @@ test_that("unreachable_code_linter works with next and break in sub expressions" foo <- function(bar) { if (bar) { next; x <- 2 + } else { + break; x <- 3 } while (bar) { break; 5 + 3 @@ -140,6 +178,9 @@ test_that("unreachable_code_linter works with next and break in sub expressions" repeat { next; test() } + for(i in 1:3) { + break; 5 + 4 + } } ") @@ -147,8 +188,10 @@ test_that("unreachable_code_linter works with next and break in sub expressions" lines, list( list(line_number = 3L, message = msg), - list(line_number = 6L, message = msg), - list(line_number = 9L, message = msg) + list(line_number = 5L, message = msg), + list(line_number = 8L, message = msg), + list(line_number = 11L, message = msg), + list(line_number = 14L, message = msg) ), linter ) From 792904c6083682429af4135958176ec62d78fdc6 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:09:59 -0700 Subject: [PATCH 17/22] fix merge on NEWS --- NEWS.md | 20 +++----------------- 1 file changed, 3 insertions(+), 17 deletions(-) diff --git a/NEWS.md b/NEWS.md index cd367feb3..e6e5d3046 100644 --- a/NEWS.md +++ b/NEWS.md @@ -49,7 +49,9 @@ * `seq_linter()` recommends `rev()` in the lint message for lints like `nrow(x):1` (#1542, @MichaelChirico). * `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. * `commas_linter()` gains an option `allow_trailing` (default `FALSE`) to allow trailing commas while indexing. (#2104, @MEO265) -* `unreachable_code_linter()` checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). +* `unreachable_code_linter()` + + checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). + + checks for unreachable code inside `if`, `else`, `for`, `while`, and `repeat` blocks, including combinations with `break` and `next` statements. (#2105, @ME0265). * `implicit_assignment_linter()` gains an argument `allow_lazy` (default `FALSE`) that allows optionally skipping lazy assignments like `A && (B <- foo(A))` (#2016, @MichaelChirico). * `unused_import_linter()` gains an argument `interpret_glue` (default `TRUE`) paralleling that in `object_usage_linter()` to toggle whether `glue::glue()` expressions should be inspected for exported object usage (#2042, @MichaelChirico). * `default_undesirable_functions` is updated to also include `Sys.unsetenv()` and `structure()` (#2192 and #2228, @IndrajeetPatil and @MichaelChirico). @@ -84,22 +86,6 @@ + `unreachable_code_linter()` + `yoda_test_linter()` * `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico). -* `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico). -* `conjunct_test_linter()` also lints usage like `dplyr::filter(x, A & B)` in favor of using `dplyr::filter(x, A, B)` unless `allow_filter = TRUE` (part of #884, @MichaelChirico; #2110, @salim-b). -* `sort_linter()` checks for code like `x == sort(x)` which is better served by using the function `is.unsorted()` (part of #884, @MichaelChirico). -* `paste_linter()` gains detection for file paths that are better constructed with `file.path()`, e.g. `paste0(dir, "/", file)` would be better as `file.path(dir, file)` (part of #884, #2082, @MichaelChirico). What exactly gets linted here can be fine-tuned with the `allow_file_path` option (`"double_slash"` by default, with alternatives `"never"` and `"always"`). When `"always"`, these rules are ignored. When `"double_slash"`, paths appearing to construct a URL that have consecutive forward slashes (`/`) are skipped. When `"never"`, even URLs should be construced with `file.path()`. -* `seq_linter()` recommends `rev()` in the lint message for lints like `nrow(x):1` (#1542, @MichaelChirico). -* `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. -* `equals_na_linter()` checks for `x %in% NA`, which is a more convoluted form of `is.na(x)` (#2088, @MichaelChirico). -* `commas_linter()` gains an option `allow_trailing` (default `FALSE`) to allow trailing commas while indexing. (#2104, @MEO265) -* `unreachable_code_linter()` - + finds unreachable code even in the presence of a comment or semicolon after `return()` or `stop()` (#2127, @MEO265). - + checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). - + checks for unreachable code inside `if`, `else`, `for`, `while`, and `repeat` blocks, including combinations with `break` and `next` statements. (#2105, @ME0265). -* `implicit_assignment_linter()` - + finds assignments in call arguments besides the first one (#2136, @MichaelChirico). - + finds assignments in parenthetical expressions like `if (A && (B <- foo(A))) { }` (#2138, @MichaelChirico). -* `inner_combine_linter()` no longer throws on length-1 calls to `c()` like `c(exp(2))` or `c(log(3))` (#2017, @MichaelChirico). Such usage is discouraged by `unnecessary_concatenation_linter()`, but `inner_combine_linter()` _per se_ does not apply. * `condition_message_linter()` ignores usages of extracted calls like `env$stop(paste(a, b))` (#1455, @MichaelChirico). * `inner_combine_linter()` no longer throws on length-1 calls to `c()` like `c(exp(2))` or `c(log(3))` (#2017, @MichaelChirico). Such usage is discouraged by `unnecessary_concatenation_linter()`, but `inner_combine_linter()` _per se_ does not apply. * `sort_linter()` only lints on `order()` of a single vector, excluding e.g. `x[order(x, y)]` and `x[order(y, x)]` (#2156, @MichaelChirico). From ce0cfa9962f73f5cd50b3177abe2689bb46de2a5 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:26:20 -0700 Subject: [PATCH 18/22] fix lint message (merge) --- tests/testthat/test-unreachable_code_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index 462488c97..bbc534d06 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -591,7 +591,7 @@ test_that("function shorthand is handled", { "), list( line_number = 3L, - message = rex::rex("Code and comments coming after a top-level return() or stop()") + message = rex::rex("Code and comments coming after a return() or stop()") ), unreachable_code_linter() ) From 4640abb5e369cf9d6b6b984b3430298f14dee323 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:26:26 -0700 Subject: [PATCH 19/22] simplify xpaths --- R/unreachable_code_linter.R | 24 +++++++++++++++--------- 1 file changed, 15 insertions(+), 9 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index b974881e2..249b9fd91 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -55,32 +55,38 @@ #' @seealso [linters] for a complete list of linters available in lintr. #' @export unreachable_code_linter <- function() { + expr_after_control <- " + (//REPEAT | //ELSE | //FOR)/following-sibling::expr[1] + | (//IF | //WHILE)/following-sibling::expr[2] + " # NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051 - xpath_return_stop <- " + xpath_return_stop <- glue(" ( - (//FUNCTION | //OP-LAMBDA | //REPEAT | //ELSE | //FOR)/following-sibling::expr - | (//IF | //WHILE)/following-sibling::expr[2] + (//FUNCTION | //OP-LAMBDA)/following-sibling::expr + | {expr_after_control} ) /expr[expr[1][ not(OP-DOLLAR or OP-AT) - and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']] + and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop'] ]] /following-sibling::*[ not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) and (not(self::COMMENT) or @line2 > preceding-sibling::*[1]/@line2) ][1] - " - xpath_next_break <- " - ((//REPEAT | //ELSE | //FOR)/following-sibling::expr | (//IF | //WHILE)/following-sibling::expr[2]) + ") + xpath_next_break <- glue(" + ({expr_after_control}) /expr[NEXT or BREAK] /following-sibling::*[ not(self::OP-RIGHT-BRACE or self::OP-SEMICOLON) and (not(self::COMMENT) or @line2 > preceding-sibling::*[1]/@line2) ][1] - " + ") xpath_if_while <- " - (//WHILE | //IF)[following-sibling::expr[1]/NUM_CONST[text() = 'FALSE']]/following-sibling::expr[2] + (//WHILE | //IF) + /following-sibling::expr[1][NUM_CONST[text() = 'FALSE']] + /following-sibling::expr[1] " xpath_else <- " From 23d3dc7622daae847be97090cbd162f368eb0085 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:31:22 -0700 Subject: [PATCH 20/22] extract to helper --- R/unreachable_code_linter.R | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index 249b9fd91..f42df276b 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -108,6 +108,13 @@ unreachable_code_linter <- function() { expr[vapply(expr, xml2::xml_length, integer(1L)) != 0L] } + # exclude comments that start with a nolint directive + drop_nolint_end_comment <- function(expr) { + is_nolint_end_comment <- xml2::xml_name(expr) == "COMMENT" & + re_matches(xml_text(expr), settings$exclude_end) + expr[!is_nolint_end_comment] + } + Linter(function(source_expression) { if (!is_lint_level(source_expression, "expression")) { return(list()) @@ -117,12 +124,8 @@ unreachable_code_linter <- function() { expr_return_stop <- xml_find_all(xml, xpath_return_stop) - # exclude comments that start with a nolint directive - is_nolint_end_comment <- xml2::xml_name(expr_return_stop) == "COMMENT" & - re_matches(xml_text(expr_return_stop), settings$exclude_end) - lints_return_stop <- xml_nodes_to_lints( - expr_return_stop[!is_nolint_end_comment], + drop_nolint_end_comment(expr_return_stop), source_expression = source_expression, lint_message = "Code and comments coming after a return() or stop() should be removed.", type = "warning" @@ -130,11 +133,8 @@ unreachable_code_linter <- function() { expr_next_break <- xml_find_all(xml, xpath_next_break) - is_nolint_end_comment <- xml2::xml_name(expr_next_break) == "COMMENT" & - re_matches(xml_text(expr_next_break), settings$exclude_end) - lints_next_break <- xml_nodes_to_lints( - expr_next_break[!is_nolint_end_comment], + drop_nolint_end_comment(expr_next_break), source_expression = source_expression, lint_message = "Code and comments coming after a `next` or `break` should be removed.", type = "warning" From 78952cfe0f9829ab800fef0bb73314e0389932f8 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:32:58 -0700 Subject: [PATCH 21/22] switch order --- R/unreachable_code_linter.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index f42df276b..498ada071 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -62,8 +62,8 @@ unreachable_code_linter <- function() { # NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051 xpath_return_stop <- glue(" ( - (//FUNCTION | //OP-LAMBDA)/following-sibling::expr - | {expr_after_control} + {expr_after_control} + | (//FUNCTION | //OP-LAMBDA)/following-sibling::expr ) /expr[expr[1][ not(OP-DOLLAR or OP-AT) From f645ac369e2b744034b71ca8673a908866a4ae94 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 8 Oct 2023 18:37:59 -0700 Subject: [PATCH 22/22] stale TODO --- tests/testthat/test-unreachable_code_linter.R | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index bbc534d06..281662b38 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -621,11 +621,5 @@ test_that("function shorthand is handled", { # }) # nolint end: commented_code_linter. -# TODO(michaelchirico): the logic could be extended to terminal if statements -# or control flows (for/while). There shouldn't really be such a thing as -# a terminal for/while (owing to ExplicitReturnLinter forcing these to -# be followed by return(invisible()) or similar), but could be included to -# catch comments for completeness / robustness as a standalone function. -# Terminal if statements are a bit messy, but would have some payoff. -# TODO(michaelchirico): again similarly, this could also apply to cases without +# TODO(michaelchirico): This could also apply to cases without # explicit returns (where it can only apply to comments)