diff --git a/DESCRIPTION b/DESCRIPTION index 7c7ec92f3..b9095f0a1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -94,6 +94,7 @@ Collate: 'fixed_regex_linter.R' 'function_argument_linter.R' 'function_left_parentheses_linter.R' + 'function_return_linter.R' 'get_source_expressions.R' 'ids_with_token.R' 'ifelse_censor_linter.R' diff --git a/NAMESPACE b/NAMESPACE index a9fdcf216..7c37237bb 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -58,6 +58,7 @@ export(extraction_operator_linter) export(fixed_regex_linter) export(function_argument_linter) export(function_left_parentheses_linter) +export(function_return_linter) export(get_r_string) export(get_source_expressions) export(ids_with_token) diff --git a/NEWS.md b/NEWS.md index 0f64838b6..80374cb3f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -29,6 +29,9 @@ can be `purrr::map(x, quantile, 0.75, na.rm = TRUE)`. Naming `probs = 0.75` can further improve readability. * `redundant_equals_linter()` for redundant comparisons to `TRUE` or `FALSE` like `is_treatment == TRUE` (#1500, @MichaelChirico) +* `function_return_linter()` for handling issues in function `return()` statements. Currently handles assignments within the `return()` + clause, e.g. `return(x <- foo())` (@MichaelChirico) + # lintr 3.0.1 * Skip multi-byte tests in non UTF-8 locales (#1504) diff --git a/R/function_return_linter.R b/R/function_return_linter.R new file mode 100644 index 000000000..4ffa8bf6d --- /dev/null +++ b/R/function_return_linter.R @@ -0,0 +1,32 @@ +#' Lint common mistakes/style issues cropping up from return statements +#' +#' `return(x <- ...)` is either distracting (because `x` is ignored), or +#' confusing (because assigning to `x` has some side effect that is muddled +#' by the dual-purpose expression). +#' +#' @evalRd rd_tags("function_return_linter") +#' @seealso [linters] for a complete list of linters available in lintr. +#' @export +function_return_linter <- function() { + xpath <- " + //SYMBOL_FUNCTION_CALL[text() = 'return'] + /parent::expr/parent::expr/expr[LEFT_ASSIGN or RIGHT_ASSIGN] + " + + Linter(function(source_expression) { + if (!is_lint_level(source_expression, "expression")) { + return(list()) + } + + xml <- source_expression$xml_parsed_content + + bad_expr <- xml2::xml_find_all(xml, xpath) + + xml_nodes_to_lints( + bad_expr, + source_expression = source_expression, + lint_message = "Move the assignment outside of the return() clause, or skip assignment altogether.", + type = "warning" + ) + }) +} diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 423ce3a7f..ef06f5e57 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -29,6 +29,7 @@ extraction_operator_linter,style best_practices fixed_regex_linter,best_practices readability efficiency function_argument_linter,style consistency best_practices function_left_parentheses_linter,style readability default +function_return_linter,readability best_practices ifelse_censor_linter,best_practices efficiency implicit_integer_linter,style consistency best_practices infix_spaces_linter,style readability default diff --git a/man/best_practices_linters.Rd b/man/best_practices_linters.Rd index 74cc203c2..7b53d924e 100644 --- a/man/best_practices_linters.Rd +++ b/man/best_practices_linters.Rd @@ -32,6 +32,7 @@ The following linters are tagged with 'best_practices': \item{\code{\link{extraction_operator_linter}}} \item{\code{\link{fixed_regex_linter}}} \item{\code{\link{function_argument_linter}}} +\item{\code{\link{function_return_linter}}} \item{\code{\link{ifelse_censor_linter}}} \item{\code{\link{implicit_integer_linter}}} \item{\code{\link{literal_coercion_linter}}} diff --git a/man/function_return_linter.Rd b/man/function_return_linter.Rd new file mode 100644 index 000000000..13aeb519e --- /dev/null +++ b/man/function_return_linter.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/function_return_linter.R +\name{function_return_linter} +\alias{function_return_linter} +\title{Lint common mistakes/style issues cropping up from return statements} +\usage{ +function_return_linter() +} +\description{ +\code{return(x <- ...)} is either distracting (because \code{x} is ignored), or +confusing (because assigning to \code{x} has some side effect that is muddled +by the dual-purpose expression). +} +\seealso{ +\link{linters} for a complete list of linters available in lintr. +} +\section{Tags}{ +\link[=best_practices_linters]{best_practices}, \link[=readability_linters]{readability} +} diff --git a/man/linters.Rd b/man/linters.Rd index 7ece255ea..14db766c0 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -17,7 +17,7 @@ see also \code{\link[=available_tags]{available_tags()}}. \section{Tags}{ The following tags exist: \itemize{ -\item{\link[=best_practices_linters]{best_practices} (39 linters)} +\item{\link[=best_practices_linters]{best_practices} (40 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (7 linters)} \item{\link[=configurable_linters]{configurable} (20 linters)} \item{\link[=consistency_linters]{consistency} (17 linters)} @@ -27,7 +27,7 @@ The following tags exist: \item{\link[=efficiency_linters]{efficiency} (18 linters)} \item{\link[=executing_linters]{executing} (5 linters)} \item{\link[=package_development_linters]{package_development} (14 linters)} -\item{\link[=readability_linters]{readability} (39 linters)} +\item{\link[=readability_linters]{readability} (40 linters)} \item{\link[=robustness_linters]{robustness} (12 linters)} \item{\link[=style_linters]{style} (36 linters)} } @@ -65,6 +65,7 @@ The following linters exist: \item{\code{\link{fixed_regex_linter}} (tags: best_practices, efficiency, readability)} \item{\code{\link{function_argument_linter}} (tags: best_practices, consistency, style)} \item{\code{\link{function_left_parentheses_linter}} (tags: default, readability, style)} +\item{\code{\link{function_return_linter}} (tags: best_practices, readability)} \item{\code{\link{ifelse_censor_linter}} (tags: best_practices, efficiency)} \item{\code{\link{implicit_integer_linter}} (tags: best_practices, consistency, style)} \item{\code{\link{infix_spaces_linter}} (tags: default, readability, style)} diff --git a/man/readability_linters.Rd b/man/readability_linters.Rd index 3cdabf926..14a06d6e0 100644 --- a/man/readability_linters.Rd +++ b/man/readability_linters.Rd @@ -25,6 +25,7 @@ The following linters are tagged with 'readability': \item{\code{\link{expect_true_false_linter}}} \item{\code{\link{fixed_regex_linter}}} \item{\code{\link{function_left_parentheses_linter}}} +\item{\code{\link{function_return_linter}}} \item{\code{\link{infix_spaces_linter}}} \item{\code{\link{inner_combine_linter}}} \item{\code{\link{line_length_linter}}} diff --git a/tests/testthat/test-function_return_linter.R b/tests/testthat/test-function_return_linter.R new file mode 100644 index 000000000..1436a15d7 --- /dev/null +++ b/tests/testthat/test-function_return_linter.R @@ -0,0 +1,68 @@ +test_that("function_return_linter skips allowed usages", { + lines_simple <- trim_some(" + foo <- function(x) { + x <- x + 1 + return(x) + } + ") + expect_lint(lines_simple, NULL, function_return_linter()) + + # arguably an expression as complicated as this should also be assigned, + # but for now that's out of the scope of this linter + lines_subassignment <- trim_some(" + foo <- function(x) { + return(x[, { + col <- col + 1 + .(grp, col) + }]) + } + ") + expect_lint(lines_subassignment, NULL, function_return_linter()) +}) + +test_that("function_return_linter blocks simple disallowed usages", { + linter <- function_return_linter() + lint_msg <- rex::rex("Move the assignment outside of the return() clause") + + expect_lint( + trim_some(" + foo <- function(x) { + return(x <- x + 1) + } + "), + lint_msg, + linter + ) + + expect_lint( + trim_some(" + foo <- function(x) { + return(x <<- x + 1) + } + "), + lint_msg, + linter + ) + + expect_lint( + trim_some(" + foo <- function(x) { + return(x + 1 -> x) + } + "), + lint_msg, + linter + ) + + side_effect_lines <- + expect_lint( + trim_some(" + e <- new.env() + foo <- function(x) { + return(e$val <- x + 1) + } + "), + lint_msg, + linter + ) +})