From c703315101501980235cb071f1f8b056f26f7032 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Fri, 17 Nov 2023 21:20:27 +0000 Subject: [PATCH 01/13] New unnecessary_nesting_linter --- DESCRIPTION | 1 + NAMESPACE | 1 + NEWS.md | 1 + R/unnecessary_nesting_linter.R | 137 +++++++++ inst/lintr/linters.csv | 1 + man/consistency_linters.Rd | 1 + man/linters.Rd | 5 +- man/readability_linters.Rd | 1 + man/unnecessary_nesting_linter.Rd | 22 ++ .../test-unnecessary_nesting_linter.R | 285 ++++++++++++++++++ 10 files changed, 453 insertions(+), 2 deletions(-) create mode 100644 R/unnecessary_nesting_linter.R create mode 100644 man/unnecessary_nesting_linter.Rd create mode 100644 tests/testthat/test-unnecessary_nesting_linter.R diff --git a/DESCRIPTION b/DESCRIPTION index 7e0f6250d..809a4b74b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -181,6 +181,7 @@ Collate: 'unnecessary_concatenation_linter.R' 'unnecessary_lambda_linter.R' 'unnecessary_nested_if_linter.R' + 'unnecessary_nesting_linter.R' 'unnecessary_placeholder_linter.R' 'unreachable_code_linter.R' 'unused_import_linter.R' diff --git a/NAMESPACE b/NAMESPACE index 8be33824d..8372b60ce 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -144,6 +144,7 @@ export(undesirable_operator_linter) export(unnecessary_concatenation_linter) export(unnecessary_lambda_linter) export(unnecessary_nested_if_linter) +export(unnecessary_nesting_linter) export(unnecessary_placeholder_linter) export(unneeded_concatenation_linter) export(unreachable_code_linter) diff --git a/NEWS.md b/NEWS.md index 477b8e61c..9582b7d5c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -15,6 +15,7 @@ * `comparison_negation_linter()` for discouraging negated comparisons when a direct negation is preferable, e.g. `!(x == y)` could be `x != y` (part of #884, @MichaelChirico). * `terminal_close_linter()` for discouraging using `close()` to end functions (part of #884, @MichaelChirico). Such usages are not robust to errors, where `close()` will not be run as intended. Put `close()` in an `on.exit()` hook, or use {withr} to manage connections with proper cleanup. * `print_linter()` for discouraging usage of `print()` on string literals like `print("Reached here")` or `print(paste("Found", nrow(DF), "rows."))` (#1894, @MichaelChirico). +* `unnecessary_nesting_linter()` for discouraging overly-nested code where an early return or eliminated sub-expression (inside '{') is preferable (part of #884, @MichaelChirico). ### Lint accuracy fixes: removing false positives diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R new file mode 100644 index 000000000..0f4aeef4f --- /dev/null +++ b/R/unnecessary_nesting_linter.R @@ -0,0 +1,137 @@ +#' Block instances of excessive nesting +#' +#' Excessive nesting harms readability. Use helper functions or early returns +#' to reduce nesting wherever possible. +#' +#' @evalRd rd_tags("unnecessary_nesting_linter") +#' @seealso +#' - [cyclocomp_linter()] for another linter that penalizes overly complexcode. +#' - [linters] for a complete list of linters available in lintr. +#' @export +unnecessary_nesting_linter <- function() { + exit_calls <- c("stop", "return", "abort", "quit", "q") + # These calls can be called in the sibling branch and not trigger a lint, + # allowing for cleanly parallel code, where breaking it would often harm readability: + # if (A) { + # stop() + # } else { + # warning() + # } + # NB: print() is intentionally excluded since its usage is usually a mistake (?print_linter) + signal_calls <- c( + exit_calls, + "warning", "warn", "message", "cat", "LOG", "stopifnot" + ) + exit_call_expr <- glue(" + expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(exit_calls)}]] + ") + # block IF here for cases where a nested if/else is entirely within + # one of the branches. + # TODO(michaelchirico): we could try and make the parallel exits requirement + # more recursive, but it's a pain to do so. + no_signal_call_expr <- glue(" + expr[ + OP-LEFT-BRACE + and expr[ + position() = last() + and not(IF) + and not(expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(signal_calls)}]]) + ] + ] + ") + # condition for ELSE should be redundant, but include for robustness + # condition on parent::expr[IF] ensures we're at the first `if` of a sequence of if/else statements + # condition on expr uses following-sibling or preceding-sibling to ensure + # that the other expr falls on a different branch (earlier used separate + # conditions on two expr[], but seems to allow any branch with >1 statement + # to lead to a lint. + # use position() = last() to ignore any expr but the last one in any branch. + if_else_exit_xpath <- glue(" + //expr[ + IF + and ELSE + and not(parent::expr[IF]) + and expr[ + OP-LEFT-BRACE + and expr[position() = last() and {exit_call_expr}] + and ( + following-sibling::{no_signal_call_expr} + or preceding-sibling::{no_signal_call_expr} + ) + ] + ] + ") + + # several carve-outs of common cases where single-expression braces are OK + # - control flow statements: if, for, while, repeat, switch() + # + switch() is unique in being a function, not a language element + # + include foreach() as a common package-based for loop extension + # - function definitions + # + includes purrr-like anonymous functions as ~ {...} + # - rlang's double-brace expressions like {{ var }} + # + NB: both braces would trigger here, so we must exclude both of them + # - any expression ending like `})` or `}]` + # + note that nesting is not improved by "fixing" such cases, + # and could also be worsened + # + motivated by the most common cases: + # * test_that("test", { expr }) + # * with(x, { expr }) / within(x, { expr }) + # * suppressWarnings({ expr }) + # * DataTable[, { expr }] + # * DataTable[, col := { expr }] <- requires carve-out for `:=` + unnecessary_brace_xpath <- " + //OP-LEFT-BRACE + /parent::expr[ + count(expr) = 1 + and not(preceding-sibling::*[ + self::FUNCTION + or self::FOR + or self::IF + or self::WHILE + or self::REPEAT + or self::expr/SYMBOL_FUNCTION_CALL[text() = 'switch'] + or self::expr/expr/SYMBOL_FUNCTION_CALL[text() = 'foreach'] + or self::OP-TILDE + or self::LEFT_ASSIGN[text() = ':='] + ]) + and not(expr/OP-LEFT-BRACE) + and not(preceding-sibling::OP-LEFT-BRACE) + and not( + OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-PAREN/@end + or OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-BRACKET/@end + ) + ] + " + + Linter(function(source_expression) { + if (!is_lint_level(source_expression, "expression")) { + return(list()) + } + + xml <- source_expression$xml_parsed_content + + if_else_exit_expr <- xml_find_all(xml, if_else_exit_xpath) + # TODO(michaelchirico): customize the error message to the exit clause used + if_else_exit_lints <- xml_nodes_to_lints( + if_else_exit_expr, + source_expression = source_expression, + lint_message = paste0( + "Reduce the nesting of this if/else statement by unnesting the ", + "portion without an exit clause (i.e., ", + paste0(exit_calls, "()", collapse = ", "), + ")." + ), + type = "warning" + ) + + unnecessary_brace_expr <- xml_find_all(xml, unnecessary_brace_xpath) + unnecessary_brace_lints <- xml_nodes_to_lints( + unnecessary_brace_expr, + source_expression = source_expression, + lint_message = "Reduce the nesting of this statement by removing the braces {}.", + type = "warning" + ) + + c(if_else_exit_lints, unnecessary_brace_lints) + }) +} diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 334f6167d..f6bff2cbd 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -101,6 +101,7 @@ undesirable_operator_linter,style efficiency configurable robustness best_practi unnecessary_concatenation_linter,style readability efficiency configurable unnecessary_lambda_linter,best_practices efficiency readability unnecessary_nested_if_linter,readability best_practices +unnecessary_nesting_linter,readability consistency unnecessary_placeholder_linter,readability best_practices unneeded_concatenation_linter,style readability efficiency configurable deprecated unreachable_code_linter,best_practices readability diff --git a/man/consistency_linters.Rd b/man/consistency_linters.Rd index 7d8a609c6..0b5e2f564 100644 --- a/man/consistency_linters.Rd +++ b/man/consistency_linters.Rd @@ -36,6 +36,7 @@ The following linters are tagged with 'consistency': \item{\code{\link{seq_linter}}} \item{\code{\link{system_file_linter}}} \item{\code{\link{T_and_F_symbol_linter}}} +\item{\code{\link{unnecessary_nesting_linter}}} \item{\code{\link{whitespace_linter}}} } } diff --git a/man/linters.Rd b/man/linters.Rd index 91d035bb0..b70127993 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -20,7 +20,7 @@ The following tags exist: \item{\link[=best_practices_linters]{best_practices} (56 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (8 linters)} \item{\link[=configurable_linters]{configurable} (34 linters)} -\item{\link[=consistency_linters]{consistency} (24 linters)} +\item{\link[=consistency_linters]{consistency} (25 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} \item{\link[=default_linters]{default} (25 linters)} \item{\link[=deprecated_linters]{deprecated} (8 linters)} @@ -28,7 +28,7 @@ The following tags exist: \item{\link[=executing_linters]{executing} (5 linters)} \item{\link[=package_development_linters]{package_development} (14 linters)} \item{\link[=pkg_testthat_linters]{pkg_testthat} (12 linters)} -\item{\link[=readability_linters]{readability} (57 linters)} +\item{\link[=readability_linters]{readability} (58 linters)} \item{\link[=robustness_linters]{robustness} (16 linters)} \item{\link[=style_linters]{style} (38 linters)} } @@ -131,6 +131,7 @@ The following linters exist: \item{\code{\link{unnecessary_concatenation_linter}} (tags: configurable, efficiency, readability, style)} \item{\code{\link{unnecessary_lambda_linter}} (tags: best_practices, efficiency, readability)} \item{\code{\link{unnecessary_nested_if_linter}} (tags: best_practices, readability)} +\item{\code{\link{unnecessary_nesting_linter}} (tags: consistency, readability)} \item{\code{\link{unnecessary_placeholder_linter}} (tags: best_practices, readability)} \item{\code{\link{unreachable_code_linter}} (tags: best_practices, readability)} \item{\code{\link{unused_import_linter}} (tags: best_practices, common_mistakes, configurable, executing)} diff --git a/man/readability_linters.Rd b/man/readability_linters.Rd index 06deb9233..24209721e 100644 --- a/man/readability_linters.Rd +++ b/man/readability_linters.Rd @@ -66,6 +66,7 @@ The following linters are tagged with 'readability': \item{\code{\link{unnecessary_concatenation_linter}}} \item{\code{\link{unnecessary_lambda_linter}}} \item{\code{\link{unnecessary_nested_if_linter}}} +\item{\code{\link{unnecessary_nesting_linter}}} \item{\code{\link{unnecessary_placeholder_linter}}} \item{\code{\link{unreachable_code_linter}}} \item{\code{\link{yoda_test_linter}}} diff --git a/man/unnecessary_nesting_linter.Rd b/man/unnecessary_nesting_linter.Rd new file mode 100644 index 000000000..3f6f9a4a6 --- /dev/null +++ b/man/unnecessary_nesting_linter.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unnecessary_nesting_linter.R +\name{unnecessary_nesting_linter} +\alias{unnecessary_nesting_linter} +\title{Block instances of excessive nesting} +\usage{ +unnecessary_nesting_linter() +} +\description{ +See \href{https://goto.google.com/c-readability-advice#avoid-unnecessary-nesting-by-using-early-returns.}{go/c-readability-advice#avoid-unnecessary-nesting-by-using-early-returns.} +This linter covers instances of excessive nesting in R code. +} +\details{ +NB: This does not apply to in-line if/else statements, which, per +\href{https://goto.google.com/rstyle#inline-statements}{go/rstyle#inline-statements}, shouldn't be in-line anyway. +} +\seealso{ +\link{linters} for a complete list of linters available in lintr. +} +\section{Tags}{ +\link[=consistency_linters]{consistency}, \link[=readability_linters]{readability} +} diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R new file mode 100644 index 000000000..1654f4c74 --- /dev/null +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -0,0 +1,285 @@ +test_that("unnecessary_nesting_linter skips allowed usages", { + linter <- unnecessary_nesting_linter() + + # parallel stops() and return()s are OK + double_stop_lines <- c( + "if (A) {", + " stop()", + "} else {", + " stop()", + "}" + ) + expect_lint(double_stop_lines, NULL, linter) + + double_return_lines <- c( + "if (A) {", + " return()", + "} else {", + " return()", + "}" + ) + expect_lint(double_return_lines, NULL, linter) +}) + +test_that("parallel stop()/warning() branches are OK", { + stop_warning_lines <- c( + "if (i == force.iter) {", + " stop(msg, call. = FALSE)", + "} else {", + " warning(attempt, call. = FALSE)", + "}" + ) + expect_lint(stop_warning_lines, NULL, unnecessary_nesting_linter()) +}) + +# TODO(michaelchirico): consider if there's a nice easy pattern to enforce for +# multiple if/else cases. This test in particular would be easy to un-nest, +# but it's not true in general. +test_that("Multiple if/else statements don't require unnesting", { + # with further branches, reducing nesting might be less readable + if_else_if_else_lines <- c( + "if (x == 'a') {", + " stop()", + "} else if (x == 'b') {", + " do_b()", + "} else {", + " stop()", + "}" + ) + expect_lint(if_else_if_else_lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("else-less if statements don't lint", { + multi_statement_if_lines <- c( + "if (x == 4) {", + " msg <- 'failed'", + " stop(msg)", + "}" + ) + expect_lint(multi_statement_if_lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("non-terminal expressions are not considered for the logic", { + multi_statement_if_lines <- c( + "if (x == 4) {", + " x <- 5", + " return(x)", + "} else {", + " return(x)", + "}" + ) + expect_lint(multi_statement_if_lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("parallels in further nesting are skipped", { + terminal_if_else_lines <- c( + "if (length(bucket) > 1) {", + " return(age)", + "} else {", + " if (grepl('[0-9]', age)) {", + " return(age)", + " } else {", + " return('unknown')", + " }", + "}" + ) + expect_lint(terminal_if_else_lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter blocks if/else with one exit branch", { + linter <- unnecessary_nesting_linter() + + if_stop_lines <- c( + "if (A) {", + " stop()", + "} else {", + " B", + "}" + ) + expect_lint( + if_stop_lines, + rex::rex("Reduce the nesting of this if/else statement by unnesting the portion"), + linter + ) + + if_return_lines <- c( + "if (A) {", + " return()", + "} else {", + " B", + "}" + ) + expect_lint( + if_return_lines, + rex::rex("Reduce the nesting of this if/else statement by unnesting the portion"), + linter + ) + + # also find exits in the later branch + else_stop_lines <- c( + "if (A) {", + " B", + "} else {", + " stop()", + "}" + ) + expect_lint( + else_stop_lines, + rex::rex("Reduce the nesting of this if/else statement by unnesting the portion"), + linter + ) + + else_return_lines <- c( + "if (A) {", + " B", + "} else {", + " return()", + "}" + ) + expect_lint( + else_return_lines, + rex::rex("Reduce the nesting of this if/else statement by unnesting the portion"), + linter + ) +}) + +test_that("unnecessary_nesting_linter skips one-line functions", { + linter <- unnecessary_nesting_linter() + + anonymous_function_lines <- c( + "foo <- function(x) {", + " return(x)", + "}" + ) + expect_lint(anonymous_function_lines, NULL, linter) + + # purrr anonymous functions also get skipped + purrr_function_lines <- c( + "purrr::map(x, ~ {", + " .x", + "})" + ) + expect_lint(purrr_function_lines, NULL, linter) +}) + +test_that("unnecessary_nesting_linter skips one-expression for loops", { + linter <- unnecessary_nesting_linter() + + for_lines <- c( + "for (i in 1:10) {", + " print(i)", + "}" + ) + expect_lint(for_lines, NULL, linter) + + # also for extended control flow functionality from packages + foreach_lines <- c( + "foreach (i = 1:10) %dopar% {", + " print(i)", + "}" + ) + expect_lint(foreach_lines, NULL, linter) +}) + +test_that("unnecessary_nesting_linter skips one-expression if and else clauses", { + lines <- c( + "if (TRUE) {", + " x", + "} else {", + " y", + "}" + ) + expect_lint(lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter skips one-expression while loops", { + lines <- c( + "while (x < 10) {", + " x <- x + 1", + "}" + ) + expect_lint(lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter skips one-expression repeat loops", { + lines <- c( + "repeat {", + " x <- x + 1", + "}" + ) + expect_lint(lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter skips one-expression switch statements", { + lines <- c( + "switch(x,", + " a = {", + " do_a()", + " },", + " b = {", + " do_b()", + " }", + ")" + ) + expect_lint(lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter passes for multi-line braced expressions", { + lines <- c( + "tryCatch(", + " {", + " foo(x)", + " bar(x)", + " },", + " error = identity", + ")" + ) + expect_lint(lines, NULL, unnecessary_nesting_linter()) +}) + +test_that("unnecessary_nesting_linter skips if unbracing won't reduce nesting", { + linter <- unnecessary_nesting_linter() + + test_that_lines <- c( + "test_that('this works', {", + " expect_true(TRUE)", + "})" + ) + expect_lint(test_that_lines, NULL, linter) + data_table_lines <- c( + "DT[, {", + " plot(x, y)", + "}]" + ) + expect_lint(data_table_lines, NULL, linter) + data_table_assign_lines <- c( + "DT[, x := {", + " foo(x, y)", + "}]" + ) + expect_lint(data_table_assign_lines, NULL, linter) +}) + +test_that("rlang's double-brace operator is skipped", { + expect_lint( + "rename(DF, col = {{ val }})", + NULL, + unnecessary_nesting_linter() + ) +}) + +test_that("unnecessary_nesting_linter blocks one-expression braced expressions", { + lines <- c( + "tryCatch(", + " {", + " foo(x)", + " },", + " error = identity", + ")" + ) + expect_lint( + lines, + R"(Reduce the nesting of this statement by removing the braces \{\}\.)", + unnecessary_nesting_linter() + ) +}) From 8398d92905d033a295c9b2d7b9a0383e8d938b84 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Fri, 17 Nov 2023 21:35:37 +0000 Subject: [PATCH 02/13] examples --- R/unnecessary_nesting_linter.R | 31 ++++++++++++++++++++++ man/unnecessary_nesting_linter.Rd | 43 ++++++++++++++++++++++++++----- 2 files changed, 68 insertions(+), 6 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 0f4aeef4f..570c35ecc 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -3,6 +3,37 @@ #' Excessive nesting harms readability. Use helper functions or early returns #' to reduce nesting wherever possible. #' +#' @examples +#' # will produce lints +#' code <- "if (A) {\n stop('A is bad!')\n} else {\n do_good()\n}" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter() +#' ) +#' +#' code <- "tryCatch(\n {\n foo()\n },\n error = identity\n)" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter() +#' ) +#' +#' # okay +#' code <- "if (A) {\n stop("A is bad because a.")\n} else {\n stop("!A is bad too.")\n}" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter() +#' ) +#' +#' code <- "capture.output({\n foo()\n})" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter() +#' ) +#' #' @evalRd rd_tags("unnecessary_nesting_linter") #' @seealso #' - [cyclocomp_linter()] for another linter that penalizes overly complexcode. diff --git a/man/unnecessary_nesting_linter.Rd b/man/unnecessary_nesting_linter.Rd index 3f6f9a4a6..8ca3c07d6 100644 --- a/man/unnecessary_nesting_linter.Rd +++ b/man/unnecessary_nesting_linter.Rd @@ -7,15 +7,46 @@ unnecessary_nesting_linter() } \description{ -See \href{https://goto.google.com/c-readability-advice#avoid-unnecessary-nesting-by-using-early-returns.}{go/c-readability-advice#avoid-unnecessary-nesting-by-using-early-returns.} -This linter covers instances of excessive nesting in R code. +Excessive nesting harms readability. Use helper functions or early returns +to reduce nesting wherever possible. } -\details{ -NB: This does not apply to in-line if/else statements, which, per -\href{https://goto.google.com/rstyle#inline-statements}{go/rstyle#inline-statements}, shouldn't be in-line anyway. +\examples{ +# will produce lints +code <- "if (A) {\n stop('A is bad!')\n} else {\n do_good()\n}" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter() +) + +code <- "tryCatch(\n {\n foo()\n },\n error = identity\n)" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter() +) + +# okay +code <- "if (A) {\n stop("A is bad because a.")\n} else {\n stop("!A is bad too.")\n}" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter() +) + +code <- "capture.output({\n foo()\n})" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter() +) + } \seealso{ -\link{linters} for a complete list of linters available in lintr. +\itemize{ +\item \code{\link[=cyclocomp_linter]{cyclocomp_linter()}} for another linter that penalizes overly complexcode. +\item \link{linters} for a complete list of linters available in lintr. +} } \section{Tags}{ \link[=consistency_linters]{consistency}, \link[=readability_linters]{readability} From cc031907f356e8f4d9fda339d2973a638e38a133 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Fri, 17 Nov 2023 21:43:49 +0000 Subject: [PATCH 03/13] bad quotes --- R/unnecessary_nesting_linter.R | 2 +- man/unnecessary_nesting_linter.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 570c35ecc..49f607a71 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -20,7 +20,7 @@ #' ) #' #' # okay -#' code <- "if (A) {\n stop("A is bad because a.")\n} else {\n stop("!A is bad too.")\n}" +#' code <- "if (A) {\n stop('A is bad because a.')\n} else {\n stop('!A is bad too.')\n}" #' writeLines(code) #' lint( #' text = code, diff --git a/man/unnecessary_nesting_linter.Rd b/man/unnecessary_nesting_linter.Rd index 8ca3c07d6..eea7ac3ce 100644 --- a/man/unnecessary_nesting_linter.Rd +++ b/man/unnecessary_nesting_linter.Rd @@ -27,7 +27,7 @@ lint( ) # okay -code <- "if (A) {\n stop("A is bad because a.")\n} else {\n stop("!A is bad too.")\n}" +code <- "if (A) {\n stop('A is bad because a.')\n} else {\n stop('!A is bad too.')\n}" writeLines(code) lint( text = code, From d5685a97880d119c91a69db03c102d3d4a85de1c Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sat, 18 Nov 2023 11:39:43 -0800 Subject: [PATCH 04/13] new test case with tryCatch() --- .../test-unnecessary_nesting_linter.R | 33 +++++++++++++------ 1 file changed, 23 insertions(+), 10 deletions(-) diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index 1654f4c74..ea45dcc37 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -269,17 +269,30 @@ test_that("rlang's double-brace operator is skipped", { }) test_that("unnecessary_nesting_linter blocks one-expression braced expressions", { - lines <- c( - "tryCatch(", - " {", - " foo(x)", - " },", - " error = identity", - ")" + linter <- unnecessary_nesting_linter() + lint_msg <- rex::rex("Reduce the nesting of this statement by removing the braces {}.") + + expect_lint( + trim_some(" + tryCatch( + { + foo(x) + }, + error = identity + ) + "), + lint_msg, + linter ) + + # NB: styler would re-style this anyway expect_lint( - lines, - R"(Reduce the nesting of this statement by removing the braces \{\}\.)", - unnecessary_nesting_linter() + trim_some(" + tryCatch({ + foo() + }, error = identity) + "), + lint_msg, + linter ) }) From dd5c98a9773db70f6de526ad8d46faa9db079462 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sat, 18 Nov 2023 17:52:10 -0800 Subject: [PATCH 05/13] '>' to mark code in comment --- R/unnecessary_nesting_linter.R | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 49f607a71..bb002dd5c 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -43,11 +43,11 @@ unnecessary_nesting_linter <- function() { exit_calls <- c("stop", "return", "abort", "quit", "q") # These calls can be called in the sibling branch and not trigger a lint, # allowing for cleanly parallel code, where breaking it would often harm readability: - # if (A) { - # stop() - # } else { - # warning() - # } + # > if (A) { + # > stop() + # > } else { + # > warning() + # > } # NB: print() is intentionally excluded since its usage is usually a mistake (?print_linter) signal_calls <- c( exit_calls, From 51b8716572fdb87e4b50de72dbefeea0083739e6 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 19 Nov 2023 11:22:14 -0800 Subject: [PATCH 06/13] interim --- tests/testthat/test-unnecessary_nesting_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index ea45dcc37..f33022d9d 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -292,7 +292,7 @@ test_that("unnecessary_nesting_linter blocks one-expression braced expressions", foo() }, error = identity) "), - lint_msg, + NULL, linter ) }) From 6211fcc3f413d45591eb140facce318f9d517bb5 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 19 Nov 2023 17:39:55 -0800 Subject: [PATCH 07/13] Treat '({' and '[{' as exemptions too --- R/unnecessary_nesting_linter.R | 6 +- .../test-unnecessary_nesting_linter.R | 72 ++++++++++++------- 2 files changed, 49 insertions(+), 29 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index bb002dd5c..8f3debe9d 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -101,7 +101,7 @@ unnecessary_nesting_linter <- function() { # + includes purrr-like anonymous functions as ~ {...} # - rlang's double-brace expressions like {{ var }} # + NB: both braces would trigger here, so we must exclude both of them - # - any expression ending like `})` or `}]` + # - any expression starting like `({` or `[{` or ending like `})` or `}]` # + note that nesting is not improved by "fixing" such cases, # and could also be worsened # + motivated by the most common cases: @@ -128,8 +128,8 @@ unnecessary_nesting_linter <- function() { and not(expr/OP-LEFT-BRACE) and not(preceding-sibling::OP-LEFT-BRACE) and not( - OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-PAREN/@end - or OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-BRACKET/@end + OP-LEFT-BRACE/@end - 1 = preceding-sibling::*[1][self::OP-LEFT-PAREN or self::OP-LEFT-BRACKET]/@end + or OP-RIGHT-BRACE/@end + 1 = following-sibling::*[1][self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACKET]/@end ) ] " diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index f33022d9d..0f2338a66 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -240,24 +240,55 @@ test_that("unnecessary_nesting_linter passes for multi-line braced expressions", test_that("unnecessary_nesting_linter skips if unbracing won't reduce nesting", { linter <- unnecessary_nesting_linter() - test_that_lines <- c( - "test_that('this works', {", - " expect_true(TRUE)", - "})" + expect_lint( + trim_some(" + test_that('this works', { + expect_true(TRUE) + }) + "), + NULL, + linter ) - expect_lint(test_that_lines, NULL, linter) - data_table_lines <- c( - "DT[, {", - " plot(x, y)", - "}]" + expect_lint( + trim_some(" + DT[, { + plot(x, y) + }] + "), + NULL, + linter ) - expect_lint(data_table_lines, NULL, linter) - data_table_assign_lines <- c( - "DT[, x := {", - " foo(x, y)", - "}]" + expect_lint( + trim_some(" + DT[, x := { + foo(x, y) + }] + "), + NULL, + linter + ) + + # NB: styler would re-style these anyway + expect_lint( + trim_some(" + tryCatch({ + foo() + }, error = identity) + "), + NULL, + linter + ) + + expect_lint( + trim_some(" + DT[{ + n <- .N - 1 + x[n] < y[n] + }, j = TRUE, by = x] + "), + NULL, + linter ) - expect_lint(data_table_assign_lines, NULL, linter) }) test_that("rlang's double-brace operator is skipped", { @@ -284,15 +315,4 @@ test_that("unnecessary_nesting_linter blocks one-expression braced expressions", lint_msg, linter ) - - # NB: styler would re-style this anyway - expect_lint( - trim_some(" - tryCatch({ - foo() - }, error = identity) - "), - NULL, - linter - ) }) From f4374b17e980c1fa1fdbd2f8ca87489efb408ad4 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Sun, 19 Nov 2023 18:18:33 -0800 Subject: [PATCH 08/13] allow_assignment argument --- R/unnecessary_nesting_linter.R | 30 ++++++++++++++-- inst/lintr/linters.csv | 2 +- man/configurable_linters.Rd | 1 + man/linters.Rd | 4 +-- man/unnecessary_nesting_linter.Rd | 26 ++++++++++++-- .../test-unnecessary_nesting_linter.R | 34 ++++++++++++++++--- 6 files changed, 84 insertions(+), 13 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 8f3debe9d..7a9eef978 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -3,6 +3,13 @@ #' Excessive nesting harms readability. Use helper functions or early returns #' to reduce nesting wherever possible. #' +#' @param allow_assignment Logical, default `TRUE`, in which case +#' braced expressions consisting only of a single assignment are skipped. +#' if `FALSE`, all braced expressions with only one child expression are linted. +#' The `TRUE` case facilitates interaction with [implicit_assignment_linter()] +#' for certain cases where an implicit assignment is necessary, so a braced +#' assignment is used to further distinguish the assignment. See examples. +#' #' @examples #' # will produce lints #' code <- "if (A) {\n stop('A is bad!')\n} else {\n do_good()\n}" @@ -19,6 +26,13 @@ #' linters = unnecessary_nesting_linter() #' ) #' +#' code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter(allow_assignment = FALSE) +#' ) +#' #' # okay #' code <- "if (A) {\n stop('A is bad because a.')\n} else {\n stop('!A is bad too.')\n}" #' writeLines(code) @@ -34,12 +48,19 @@ #' linters = unnecessary_nesting_linter() #' ) #' +#' code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = unnecessary_nesting_linter() +#' ) +#' #' @evalRd rd_tags("unnecessary_nesting_linter") #' @seealso #' - [cyclocomp_linter()] for another linter that penalizes overly complexcode. #' - [linters] for a complete list of linters available in lintr. #' @export -unnecessary_nesting_linter <- function() { +unnecessary_nesting_linter <- function(allow_assignment = TRUE) { exit_calls <- c("stop", "return", "abort", "quit", "q") # These calls can be called in the sibling branch and not trigger a lint, # allowing for cleanly parallel code, where breaking it would often harm readability: @@ -93,6 +114,8 @@ unnecessary_nesting_linter <- function() { ] ") + assignment_cond <- if (allow_assignment) "expr[LEFT_ASSIGN or RIGHT_ASSIGN]" else "false" + # several carve-outs of common cases where single-expression braces are OK # - control flow statements: if, for, while, repeat, switch() # + switch() is unique in being a function, not a language element @@ -110,7 +133,7 @@ unnecessary_nesting_linter <- function() { # * suppressWarnings({ expr }) # * DataTable[, { expr }] # * DataTable[, col := { expr }] <- requires carve-out for `:=` - unnecessary_brace_xpath <- " + unnecessary_brace_xpath <- glue(" //OP-LEFT-BRACE /parent::expr[ count(expr) = 1 @@ -131,8 +154,9 @@ unnecessary_nesting_linter <- function() { OP-LEFT-BRACE/@end - 1 = preceding-sibling::*[1][self::OP-LEFT-PAREN or self::OP-LEFT-BRACKET]/@end or OP-RIGHT-BRACE/@end + 1 = following-sibling::*[1][self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACKET]/@end ) + and not({assignment_cond}) ] - " + ") Linter(function(source_expression) { if (!is_lint_level(source_expression, "expression")) { diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 1a2a374ac..c8be1b9c0 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -108,7 +108,7 @@ undesirable_operator_linter,style efficiency configurable robustness best_practi unnecessary_concatenation_linter,style readability efficiency configurable unnecessary_lambda_linter,best_practices efficiency readability unnecessary_nested_if_linter,readability best_practices -unnecessary_nesting_linter,readability consistency +unnecessary_nesting_linter,readability consistency configurable unnecessary_placeholder_linter,readability best_practices unneeded_concatenation_linter,style readability efficiency configurable deprecated unreachable_code_linter,best_practices readability diff --git a/man/configurable_linters.Rd b/man/configurable_linters.Rd index 0f5adb229..9cd5a836a 100644 --- a/man/configurable_linters.Rd +++ b/man/configurable_linters.Rd @@ -46,6 +46,7 @@ The following linters are tagged with 'configurable': \item{\code{\link{undesirable_function_linter}}} \item{\code{\link{undesirable_operator_linter}}} \item{\code{\link{unnecessary_concatenation_linter}}} +\item{\code{\link{unnecessary_nesting_linter}}} \item{\code{\link{unused_import_linter}}} } } diff --git a/man/linters.Rd b/man/linters.Rd index 4c8d3bd6f..c0e432522 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -19,7 +19,7 @@ The following tags exist: \itemize{ \item{\link[=best_practices_linters]{best_practices} (62 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (10 linters)} -\item{\link[=configurable_linters]{configurable} (35 linters)} +\item{\link[=configurable_linters]{configurable} (36 linters)} \item{\link[=consistency_linters]{consistency} (29 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} \item{\link[=default_linters]{default} (25 linters)} @@ -139,7 +139,7 @@ The following linters exist: \item{\code{\link{unnecessary_concatenation_linter}} (tags: configurable, efficiency, readability, style)} \item{\code{\link{unnecessary_lambda_linter}} (tags: best_practices, efficiency, readability)} \item{\code{\link{unnecessary_nested_if_linter}} (tags: best_practices, readability)} -\item{\code{\link{unnecessary_nesting_linter}} (tags: consistency, readability)} +\item{\code{\link{unnecessary_nesting_linter}} (tags: configurable, consistency, readability)} \item{\code{\link{unnecessary_placeholder_linter}} (tags: best_practices, readability)} \item{\code{\link{unreachable_code_linter}} (tags: best_practices, readability)} \item{\code{\link{unused_import_linter}} (tags: best_practices, common_mistakes, configurable, executing)} diff --git a/man/unnecessary_nesting_linter.Rd b/man/unnecessary_nesting_linter.Rd index eea7ac3ce..fd491de38 100644 --- a/man/unnecessary_nesting_linter.Rd +++ b/man/unnecessary_nesting_linter.Rd @@ -4,7 +4,15 @@ \alias{unnecessary_nesting_linter} \title{Block instances of excessive nesting} \usage{ -unnecessary_nesting_linter() +unnecessary_nesting_linter(allow_assignment = TRUE) +} +\arguments{ +\item{allow_assignment}{Logical, default \code{TRUE}, in which case +braced expressions consisting only of a single assignment are skipped. +if \code{FALSE}, all braced expressions with only one child expression are linted. +The \code{TRUE} case facilitates interaction with \code{\link[=implicit_assignment_linter]{implicit_assignment_linter()}} +for certain cases where an implicit assignment is necessary, so a braced +assignment is used to further distinguish the assignment. See examples.} } \description{ Excessive nesting harms readability. Use helper functions or early returns @@ -26,6 +34,13 @@ lint( linters = unnecessary_nesting_linter() ) +code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter(allow_assignment = FALSE) +) + # okay code <- "if (A) {\n stop('A is bad because a.')\n} else {\n stop('!A is bad too.')\n}" writeLines(code) @@ -41,6 +56,13 @@ lint( linters = unnecessary_nesting_linter() ) +code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)" +writeLines(code) +lint( + text = code, + linters = unnecessary_nesting_linter() +) + } \seealso{ \itemize{ @@ -49,5 +71,5 @@ lint( } } \section{Tags}{ -\link[=consistency_linters]{consistency}, \link[=readability_linters]{readability} +\link[=configurable_linters]{configurable}, \link[=consistency_linters]{consistency}, \link[=readability_linters]{readability} } diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index 0f2338a66..3f5a2034b 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -224,6 +224,18 @@ test_that("unnecessary_nesting_linter skips one-expression switch statements", { expect_lint(lines, NULL, unnecessary_nesting_linter()) }) +test_that("unnecessary_nesting_linter skips one-expression assignments by default", { + expect_lint( + trim_some(" + { + x <- foo() + } + "), + NULL, + unnecessary_nesting_linter() + ) +}) + test_that("unnecessary_nesting_linter passes for multi-line braced expressions", { lines <- c( "tryCatch(", @@ -300,9 +312,6 @@ test_that("rlang's double-brace operator is skipped", { }) test_that("unnecessary_nesting_linter blocks one-expression braced expressions", { - linter <- unnecessary_nesting_linter() - lint_msg <- rex::rex("Reduce the nesting of this statement by removing the braces {}.") - expect_lint( trim_some(" tryCatch( @@ -312,7 +321,22 @@ test_that("unnecessary_nesting_linter blocks one-expression braced expressions", error = identity ) "), - lint_msg, - linter + rex::rex("Reduce the nesting of this statement by removing the braces {}."), + unnecessary_nesting_linter() + ) +}) + +test_that("unnecessary_nesting_linter allow_assignment= argument works", { + expect_lint( + trim_some(" + tryCatch( + { + idx <- foo(x) + }, + error = identity + ) + "), + rex::rex("Reduce the nesting of this statement by removing the braces {}."), + unnecessary_nesting_linter(allow_assignment = FALSE) ) }) From 35ab376d3ec1204c02dd6da220178bb02b3b336c Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 05:07:24 +0000 Subject: [PATCH 09/13] defer implementing parallel warning (etc) branches for now --- R/unnecessary_nesting_linter.R | 22 +++++-------------- .../test-unnecessary_nesting_linter.R | 11 ---------- 2 files changed, 5 insertions(+), 28 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 7a9eef978..3cf6a68ae 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -62,32 +62,20 @@ #' @export unnecessary_nesting_linter <- function(allow_assignment = TRUE) { exit_calls <- c("stop", "return", "abort", "quit", "q") - # These calls can be called in the sibling branch and not trigger a lint, - # allowing for cleanly parallel code, where breaking it would often harm readability: - # > if (A) { - # > stop() - # > } else { - # > warning() - # > } - # NB: print() is intentionally excluded since its usage is usually a mistake (?print_linter) - signal_calls <- c( - exit_calls, - "warning", "warn", "message", "cat", "LOG", "stopifnot" - ) exit_call_expr <- glue(" - expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(exit_calls)}]] + expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(exit_calls)}]] ") # block IF here for cases where a nested if/else is entirely within # one of the branches. # TODO(michaelchirico): we could try and make the parallel exits requirement # more recursive, but it's a pain to do so. - no_signal_call_expr <- glue(" + no_exit_call_expr <- glue(" expr[ OP-LEFT-BRACE and expr[ position() = last() and not(IF) - and not(expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(signal_calls)}]]) + and not(expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(exit_calls)}]]) ] ] ") @@ -107,8 +95,8 @@ unnecessary_nesting_linter <- function(allow_assignment = TRUE) { OP-LEFT-BRACE and expr[position() = last() and {exit_call_expr}] and ( - following-sibling::{no_signal_call_expr} - or preceding-sibling::{no_signal_call_expr} + following-sibling::{no_exit_call_expr} + or preceding-sibling::{no_exit_call_expr} ) ] ] diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index 3f5a2034b..2ff99af93 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -21,17 +21,6 @@ test_that("unnecessary_nesting_linter skips allowed usages", { expect_lint(double_return_lines, NULL, linter) }) -test_that("parallel stop()/warning() branches are OK", { - stop_warning_lines <- c( - "if (i == force.iter) {", - " stop(msg, call. = FALSE)", - "} else {", - " warning(attempt, call. = FALSE)", - "}" - ) - expect_lint(stop_warning_lines, NULL, unnecessary_nesting_linter()) -}) - # TODO(michaelchirico): consider if there's a nice easy pattern to enforce for # multiple if/else cases. This test in particular would be easy to un-nest, # but it's not true in general. From 8c3bb7a8a76509246e5f1e284f684180d72102f4 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 06:49:09 +0000 Subject: [PATCH 10/13] finish merge --- man/linters.Rd | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/man/linters.Rd b/man/linters.Rd index f5e9346bb..26fef3fee 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -19,8 +19,8 @@ The following tags exist: \itemize{ \item{\link[=best_practices_linters]{best_practices} (63 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (10 linters)} -\item{\link[=configurable_linters]{configurable} (37 linters)} -\item{\link[=consistency_linters]{consistency} (31 linters)} +\item{\link[=configurable_linters]{configurable} (38 linters)} +\item{\link[=consistency_linters]{consistency} (32 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} \item{\link[=default_linters]{default} (25 linters)} \item{\link[=deprecated_linters]{deprecated} (4 linters)} @@ -28,7 +28,7 @@ The following tags exist: \item{\link[=executing_linters]{executing} (6 linters)} \item{\link[=package_development_linters]{package_development} (14 linters)} \item{\link[=pkg_testthat_linters]{pkg_testthat} (12 linters)} -\item{\link[=readability_linters]{readability} (64 linters)} +\item{\link[=readability_linters]{readability} (65 linters)} \item{\link[=regex_linters]{regex} (4 linters)} \item{\link[=robustness_linters]{robustness} (17 linters)} \item{\link[=style_linters]{style} (39 linters)} From 9ff5503553d687704f5dd5e647e5a3e77ab4e301 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 07:28:46 +0000 Subject: [PATCH 11/13] TODOs->tracker --- R/unnecessary_nesting_linter.R | 3 --- 1 file changed, 3 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 3cf6a68ae..05fb6af8c 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -67,8 +67,6 @@ unnecessary_nesting_linter <- function(allow_assignment = TRUE) { ") # block IF here for cases where a nested if/else is entirely within # one of the branches. - # TODO(michaelchirico): we could try and make the parallel exits requirement - # more recursive, but it's a pain to do so. no_exit_call_expr <- glue(" expr[ OP-LEFT-BRACE @@ -154,7 +152,6 @@ unnecessary_nesting_linter <- function(allow_assignment = TRUE) { xml <- source_expression$xml_parsed_content if_else_exit_expr <- xml_find_all(xml, if_else_exit_xpath) - # TODO(michaelchirico): customize the error message to the exit clause used if_else_exit_lints <- xml_nodes_to_lints( if_else_exit_expr, source_expression = source_expression, From 50569e1dfa20c25fb41ad1e8c89c79ca8c45508b Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 07:29:19 +0000 Subject: [PATCH 12/13] Rd wording --- R/unnecessary_nesting_linter.R | 2 +- man/unnecessary_nesting_linter.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 05fb6af8c..8e92e42dd 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -1,4 +1,4 @@ -#' Block instances of excessive nesting +#' Block instances of unnecessary nesting #' #' Excessive nesting harms readability. Use helper functions or early returns #' to reduce nesting wherever possible. diff --git a/man/unnecessary_nesting_linter.Rd b/man/unnecessary_nesting_linter.Rd index fd491de38..484097017 100644 --- a/man/unnecessary_nesting_linter.Rd +++ b/man/unnecessary_nesting_linter.Rd @@ -2,7 +2,7 @@ % Please edit documentation in R/unnecessary_nesting_linter.R \name{unnecessary_nesting_linter} \alias{unnecessary_nesting_linter} -\title{Block instances of excessive nesting} +\title{Block instances of unnecessary nesting} \usage{ unnecessary_nesting_linter(allow_assignment = TRUE) } From 2efcafb67e9ca82266bb528a8ecb3cd14fdf08b5 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 21 Nov 2023 23:29:59 +0000 Subject: [PATCH 13/13] disable switch() for now --- R/unnecessary_nesting_linter.R | 7 ++----- tests/testthat/test-unnecessary_nesting_linter.R | 14 -------------- 2 files changed, 2 insertions(+), 19 deletions(-) diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 8e92e42dd..5fa89fc04 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -103,16 +103,14 @@ unnecessary_nesting_linter <- function(allow_assignment = TRUE) { assignment_cond <- if (allow_assignment) "expr[LEFT_ASSIGN or RIGHT_ASSIGN]" else "false" # several carve-outs of common cases where single-expression braces are OK - # - control flow statements: if, for, while, repeat, switch() - # + switch() is unique in being a function, not a language element + # - control flow statements: if, for, while, repeat # + include foreach() as a common package-based for loop extension # - function definitions # + includes purrr-like anonymous functions as ~ {...} # - rlang's double-brace expressions like {{ var }} # + NB: both braces would trigger here, so we must exclude both of them # - any expression starting like `({` or `[{` or ending like `})` or `}]` - # + note that nesting is not improved by "fixing" such cases, - # and could also be worsened + # + note that nesting is not improved by "fixing" such cases, and could also be worsened # + motivated by the most common cases: # * test_that("test", { expr }) # * with(x, { expr }) / within(x, { expr }) @@ -129,7 +127,6 @@ unnecessary_nesting_linter <- function(allow_assignment = TRUE) { or self::IF or self::WHILE or self::REPEAT - or self::expr/SYMBOL_FUNCTION_CALL[text() = 'switch'] or self::expr/expr/SYMBOL_FUNCTION_CALL[text() = 'foreach'] or self::OP-TILDE or self::LEFT_ASSIGN[text() = ':='] diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index 2ff99af93..5180384a8 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -199,20 +199,6 @@ test_that("unnecessary_nesting_linter skips one-expression repeat loops", { expect_lint(lines, NULL, unnecessary_nesting_linter()) }) -test_that("unnecessary_nesting_linter skips one-expression switch statements", { - lines <- c( - "switch(x,", - " a = {", - " do_a()", - " },", - " b = {", - " do_b()", - " }", - ")" - ) - expect_lint(lines, NULL, unnecessary_nesting_linter()) -}) - test_that("unnecessary_nesting_linter skips one-expression assignments by default", { expect_lint( trim_some("