diff --git a/NEWS.md b/NEWS.md index c7bb1d938..e49c0bf93 100644 --- a/NEWS.md +++ b/NEWS.md @@ -22,7 +22,7 @@ ## Changes to default linters -* New default linter `return_linter()` for the style guide rule that terminal returns should be left implicit (#1100, #2354, and #2356, @MEO265 and @MichaelChirico). +* New default linter `return_linter()` for the style guide rule that terminal returns should be left implicit (#1100, #2343, #2354, and #2356, @MEO265 and @MichaelChirico). ## New and improved features diff --git a/R/return_linter.R b/R/return_linter.R index fd3dd5831..a0e1c245f 100644 --- a/R/return_linter.R +++ b/R/return_linter.R @@ -8,7 +8,8 @@ #' explicitly supplied. #' @param allow_implicit_else Logical, default `TRUE`. If `FALSE`, functions with a terminal #' `if` clause must always have an `else` clause, making the `NULL` alternative explicit -#' if necessary. +#' if necessary. Similarly, functions with terminal [switch()] statements must have an +#' explicit default case. #' @param return_functions Character vector of functions that are accepted as terminal calls #' when `return_style = "explicit"`. These are in addition to exit functions #' from base that are always allowed: [stop()], [q()], [quit()], [invokeRestart()], @@ -178,36 +179,14 @@ nested_return_lints <- function(expr, params) { if (length(child_expr) == 0L) { return(list()) } - child_node <- xml_name(child_expr) - - if (child_node[1L] == "OP-LEFT-BRACE") { - expr_idx <- which(child_node %in% c("expr", "equal_assign", "expr_or_assign_or_help")) - if (length(expr_idx) == 0L) { # empty brace expression {} - if (params$implicit) { - return(list()) - } else { - return(list(xml_nodes_to_lints( - expr, - source_expression = params$source_expression, - lint_message = params$lint_message, - type = params$type - ))) - } - } - nested_return_lints(child_expr[[tail(expr_idx, 1L)]], params) - } else if (child_node[1L] == "IF") { - expr_idx <- which(child_node %in% c("expr", "equal_assign", "expr_or_assign_or_help")) - return_lints <- lapply(child_expr[expr_idx[-1L]], nested_return_lints, params) - if (params$allow_implicit_else || length(expr_idx) == 3L) { - return(return_lints) - } - implicit_else_lints <- list(xml_nodes_to_lints( - expr, - source_expression = params$source_expression, - lint_message = "All functions with terminal if statements must have a corresponding terminal else clause", - type = "warning" - )) - c(return_lints, implicit_else_lints) + names(child_expr) <- xml_name(child_expr) + + if (names(child_expr)[1L] == "OP-LEFT-BRACE") { + brace_return_lints(child_expr, expr, params) + } else if (names(child_expr)[1L] == "IF") { + if_return_lints(child_expr, expr, params) + } else if (!is.na(xml_find_first(expr, "expr/SYMBOL_FUNCTION_CALL[text() = 'switch']"))) { + switch_return_lints(child_expr, expr, params) } else { xml_nodes_to_lints( xml_find_first(child_expr[[1L]], params$lint_xpath), @@ -217,3 +196,53 @@ nested_return_lints <- function(expr, params) { ) } } + +brace_return_lints <- function(child_expr, expr, params) { + expr_idx <- which(names(child_expr) %in% c("expr", "equal_assign", "expr_or_assign_or_help")) + if (length(expr_idx) == 0L) { # empty brace expression {} + if (params$implicit) { + return(list()) + } else { + return(list(xml_nodes_to_lints( + expr, + source_expression = params$source_expression, + lint_message = params$lint_message, + type = params$type + ))) + } + } + nested_return_lints(child_expr[[tail(expr_idx, 1L)]], params) +} + +if_return_lints <- function(child_expr, expr, params) { + expr_idx <- which(names(child_expr) %in% c("expr", "equal_assign", "expr_or_assign_or_help")) + return_lints <- lapply(child_expr[expr_idx[-1L]], nested_return_lints, params) + if (params$allow_implicit_else || length(expr_idx) == 3L) { + return(return_lints) + } + implicit_else_lints <- list(xml_nodes_to_lints( + expr, + source_expression = params$source_expression, + lint_message = "All functions with terminal if statements must have a corresponding terminal else clause.", + type = "warning" + )) + c(return_lints, implicit_else_lints) +} + +switch_return_lints <- function(child_expr, expr, params) { + # equal_assign/expr_or_assign_or_help not possible here + expr_idx <- which(names(child_expr) == "expr") + # switch(x, ...) | expr[1]: switch; expr[2]: x. Drop the first two, check usage in ... + return_lints <- lapply(child_expr[tail(expr_idx, -2L)], nested_return_lints, params) + # in addition to the two dropped above, a third unmatched would be the default case. + if (params$allow_implicit_else || length(expr_idx) - sum(names(child_expr) == "EQ_SUB") == 3L) { + return(return_lints) + } + implicit_else_lints <- list(xml_nodes_to_lints( + expr, + source_expression = params$source_expression, + lint_message = "All functions with terminal switch statements must have a terminal default clause.", + type = "warning" + )) + c(return_lints, implicit_else_lints) +} diff --git a/man/return_linter.Rd b/man/return_linter.Rd index fc4fdbab0..0e99df289 100644 --- a/man/return_linter.Rd +++ b/man/return_linter.Rd @@ -20,7 +20,8 @@ explicitly supplied.} \item{allow_implicit_else}{Logical, default \code{TRUE}. If \code{FALSE}, functions with a terminal \code{if} clause must always have an \verb{else} clause, making the \code{NULL} alternative explicit -if necessary.} +if necessary. Similarly, functions with terminal \code{\link[=switch]{switch()}} statements must have an +explicit default case.} \item{return_functions}{Character vector of functions that are accepted as terminal calls when \code{return_style = "explicit"}. These are in addition to exit functions diff --git a/tests/testthat/test-return_linter.R b/tests/testthat/test-return_linter.R index a284193bd..b05b3abd3 100644 --- a/tests/testthat/test-return_linter.R +++ b/tests/testthat/test-return_linter.R @@ -166,56 +166,6 @@ test_that("Do not lint stop on end of function", { ) }) -test_that("Do not lint stop on end of function", { - linter <- return_linter(return_style = "explicit") - lint_msg <- rex::rex("All functions must have an explicit return().") - - expect_lint( - trim_some(" - function(x) { - switch(x, a = 1, 'b' = 2, '3' = 3, 4) - } - "), - list(lint_msg, line_number = 2L), - linter - ) - - expect_lint( - trim_some(" - function(x) { - switch(x, a = return(1), 'b' = stop(2), '3' = return(3), 4) - } - "), - list(lint_msg, line_number = 2L), - linter - ) - - expect_lint( - trim_some(" - function() { - switch( - x, - a = return(1), - 'b' = stop(2), - '3' = return(3) - ) - } - "), - list(lint_msg, line_number = 2L), - linter - ) - - expect_lint( - trim_some(" - function(x) { - switch(x, a = return(1), 'b' = stop(2), '3' = return(3), stop('End')) - } - "), - list(lint_msg, line_number = 2L), - linter - ) -}) - test_that("return_linter works in simple function", { expect_lint( trim_some(" @@ -1587,3 +1537,290 @@ test_that("= assignments are handled correctly", { implicit_linter ) }) + +test_that("terminal switch() is handled correctly", { + implicit_linter <- return_linter() + implicit_msg <- rex::rex("Use implicit return behavior; explicit return() is not needed.") + explicit_linter <- return_linter(return_style = "explicit") + explicit_msg <- rex::rex("All functions must have an explicit return().") + + no_return_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = 1, + b = 2 + ) + } + ") + expect_lint(no_return_lines, NULL, implicit_linter) + expect_lint(no_return_lines, list(explicit_msg, explicit_msg), explicit_linter) + + outer_return_lines <- trim_some(" + foo <- function(x) { + return(switch(x, + a = 1, + b = 2 + )) + } + ") + expect_lint(outer_return_lines, implicit_msg, implicit_linter) + expect_lint(outer_return_lines, NULL, explicit_linter) + + partial_return_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = return(1), + b = 2 + ) + } + ") + expect_lint(partial_return_lines, implicit_msg, implicit_linter) + expect_lint(partial_return_lines, explicit_msg, explicit_linter) + + all_return_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = return(1), + b = return(2) + ) + } + ") + expect_lint(all_return_lines, list(implicit_msg, implicit_msg), implicit_linter) + expect_lint(all_return_lines, NULL, explicit_linter) + + default_all_return_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = return(1), + return(2) + ) + } + ") + expect_lint(default_all_return_lines, list(implicit_msg, implicit_msg), implicit_linter) + expect_lint(default_all_return_lines, NULL, explicit_linter) + + default_no_return_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = 1, + 2 + ) + } + ") + expect_lint(default_no_return_lines, NULL, implicit_linter) + expect_lint(default_no_return_lines, list(explicit_msg, explicit_msg), explicit_linter) + + no_return_braced_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = { + 1 + 2 + 3 + 4 + }, + b = { + 5 + 6 + 7 + } + ) + } + ") + expect_lint(no_return_braced_lines, NULL, implicit_linter) + expect_lint( + no_return_braced_lines, + list( + list(explicit_msg, line_number = 7L), + list(explicit_msg, line_number = 12L) + ), + explicit_linter + ) + + all_return_braced_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = { + 1 + 2 + 3 + return(4) + }, + b = { + 5 + 6 + return(7) + } + ) + } + ") + expect_lint( + all_return_braced_lines, + list( + list(implicit_msg, line_number = 7L), + list(implicit_msg, line_number = 12L) + ), + implicit_linter + ) + expect_lint(all_return_braced_lines, NULL, explicit_linter) + + early_return_braced_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = { + 1 + if (TRUE) { + return(2) + } + 3 + 4 + }, + b = { + 5 + 6 + 7 + } + ) + } + ") + expect_lint(early_return_braced_lines, NULL, implicit_linter) + expect_lint( + early_return_braced_lines, + list( + list(explicit_msg, line_number = 9L), + list(explicit_msg, line_number = 14L) + ), + explicit_linter + ) + + if_no_return_braced_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = { + 1 + if (TRUE) { + 2 + } else { + 3 + } + }, + b = { + 5 + 6 + 7 + } + ) + } + ") + expect_lint(if_no_return_braced_lines, NULL, implicit_linter) + expect_lint( + if_no_return_braced_lines, + list( + list(explicit_msg, line_number = 6L), + list(explicit_msg, line_number = 8L), + list(explicit_msg, line_number = 14L) + ), + explicit_linter + ) + + if_return_braced_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = { + 1 + if (TRUE) { + return(2) + } else { + return(3) + } + }, + b = { + 5 + 6 + return(7) + } + ) + } + ") + expect_lint( + if_return_braced_lines, + list( + list(implicit_msg, line_number = 6L), + list(implicit_msg, line_number = 8L), + list(implicit_msg, line_number = 14L) + ), + implicit_linter + ) + expect_lint(if_return_braced_lines, NULL, explicit_linter) + + ok_exit_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = .Call(a_routine, x), + b = .Call(b_routine, x), + stop('invalid') + ) + } + ") + expect_lint(ok_exit_lines, NULL, implicit_linter) + expect_lint(ok_exit_lines, NULL, explicit_linter) +}) + +test_that("switch() default statements interact with allow_implicit_else", { + implicit_linter <- return_linter(allow_implicit_else = FALSE) + explicit_linter <- return_linter(allow_implicit_else = FALSE, return_style = "explicit") + implicit_msg <- rex::rex("Use implicit return behavior; explicit return() is not needed.") + explicit_msg <- rex::rex("All functions must have an explicit return().") + implicit_switch_msg <- rex::rex("All functions with terminal switch statements") + implicit_else_msg <- rex::rex("All functions with terminal if statements") + + no_default_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = 1, + b = 2 + ) + } + ") + expect_lint(no_default_lines, list(implicit_switch_msg, line_number = 2L), implicit_linter) + expect_lint(no_default_lines, list(implicit_switch_msg, explicit_msg, explicit_msg), explicit_linter) + + ifelse_default_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = 1, + b = 2, + if (x != 'c') { + 3 + } else { + 4 + } + ) + } + ") + expect_lint(ifelse_default_lines, NULL, implicit_linter) + expect_lint(ifelse_default_lines, list(explicit_msg, explicit_msg, explicit_msg, explicit_msg), explicit_linter) + + if_no_else_default_lines <- trim_some(" + foo <- function(x) { + switch(x, + a = 1, + b = 2, + if (x != 'c') { + 3 + } + ) + } + ") + expect_lint(if_no_else_default_lines, list(implicit_else_msg, line_number = 5L), implicit_linter) + expect_lint( + if_no_else_default_lines, + list( + list(explicit_msg, line_number = 3L), + list(explicit_msg, line_number = 4L), + list(implicit_else_msg, line_number = 5L), + list(explicit_msg, line_number = 6L) + ), + explicit_linter + ) +})