diff --git a/DESCRIPTION b/DESCRIPTION index 177daed02..66840417c 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -152,6 +152,7 @@ Collate: 'pipe_call_linter.R' 'pipe_consistency_linter.R' 'pipe_continuation_linter.R' + 'pipe_return_linter.R' 'print_linter.R' 'quotes_linter.R' 'redundant_equals_linter.R' diff --git a/NAMESPACE b/NAMESPACE index 2a4c128a9..5da1db531 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -115,6 +115,7 @@ export(paste_linter) export(pipe_call_linter) export(pipe_consistency_linter) export(pipe_continuation_linter) +export(pipe_return_linter) export(print_linter) export(quotes_linter) export(redundant_equals_linter) diff --git a/NEWS.md b/NEWS.md index 123f9fccd..d5a8ec1e1 100644 --- a/NEWS.md +++ b/NEWS.md @@ -30,6 +30,7 @@ * `which_grepl_linter()` for discouraging `which(grepl(ptn, x))` in favor of directly using `grep(ptn, x)` (part of #884, @MichaelChirico). * `list_comparison_linter()` for discouraging comparisons on the output of `lapply()`, e.g. `lapply(x, sum) > 10` (part of #884, @MichaelChirico). * `print_linter()` for discouraging usage of `print()` on string literals like `print("Reached here")` or `print(paste("Found", nrow(DF), "rows."))` (#1894, @MichaelChirico). +* `pipe_return_linter()` for discouraging usage of `return()` inside a {magrittr} pipeline (part of #884, @MichaelChirico). ### Lint accuracy fixes: removing false positives diff --git a/R/pipe_return_linter.R b/R/pipe_return_linter.R new file mode 100644 index 000000000..fd73da8ae --- /dev/null +++ b/R/pipe_return_linter.R @@ -0,0 +1,39 @@ +#' Block usage of return() in magrittr pipelines +#' +#' [return()] inside a magrittr pipeline does not actually execute `return()` +#' like you'd expect: `\(x) { x %>% return(); FALSE }` will return `FALSE`! +#' It will technically work "as expected" if this is the final statement +#' in the function body, but such usage is misleading. Instead, assign +#' the pipe outcome to a variable and return that. +#' +#' @examples +#' # will produce lints +#' lint( +#' text = "function(x) x %>% return()", +#' linters = pipe_return_linter() +#' ) +#' +#' # okay +#' code <- "function(x) {\n y <- sum(x)\n return(y)\n}" +#' writeLines(code) +#' lint( +#' text = code, +#' linters = pipe_return_linter() +#' ) +#' +#' @evalRd rd_tags("pipe_return_linter") +#' @seealso [linters] for a complete list of linters available in lintr. +#' @export +pipe_return_linter <- make_linter_from_xpath( + # NB: Native pipe disallows this at the parser level, so there's no need + # to lint in valid R code. + xpath = " + //SPECIAL[text() = '%>%'] + /following-sibling::expr[expr/SYMBOL_FUNCTION_CALL[text() = 'return']] + ", + lint_message = paste( + "Using return() as the final step of a magrittr pipeline", + "is an anti-pattern. Instead, assign the output of the pipeline to", + "a well-named object and return that." + ) +) diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 866247a62..db692cbf3 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -72,6 +72,7 @@ paste_linter,best_practices consistency configurable pipe_call_linter,style readability pipe_consistency_linter,style readability configurable pipe_continuation_linter,style readability default +pipe_return_linter,best_practices common_mistakes print_linter,best_practices consistency quotes_linter,style consistency readability default configurable redundant_equals_linter,best_practices readability efficiency common_mistakes diff --git a/man/best_practices_linters.Rd b/man/best_practices_linters.Rd index 821acc0c2..322f5736d 100644 --- a/man/best_practices_linters.Rd +++ b/man/best_practices_linters.Rd @@ -49,6 +49,7 @@ The following linters are tagged with 'best_practices': \item{\code{\link{nzchar_linter}}} \item{\code{\link{outer_negation_linter}}} \item{\code{\link{paste_linter}}} +\item{\code{\link{pipe_return_linter}}} \item{\code{\link{print_linter}}} \item{\code{\link{redundant_equals_linter}}} \item{\code{\link{redundant_ifelse_linter}}} diff --git a/man/common_mistakes_linters.Rd b/man/common_mistakes_linters.Rd index b21480c12..d3578e567 100644 --- a/man/common_mistakes_linters.Rd +++ b/man/common_mistakes_linters.Rd @@ -18,6 +18,7 @@ The following linters are tagged with 'common_mistakes': \item{\code{\link{list_comparison_linter}}} \item{\code{\link{missing_argument_linter}}} \item{\code{\link{missing_package_linter}}} +\item{\code{\link{pipe_return_linter}}} \item{\code{\link{redundant_equals_linter}}} \item{\code{\link{sprintf_linter}}} \item{\code{\link{unused_import_linter}}} diff --git a/man/linters.Rd b/man/linters.Rd index 2b4498678..6af6dd0a8 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -17,8 +17,8 @@ see also \code{\link[=available_tags]{available_tags()}}. \section{Tags}{ The following tags exist: \itemize{ -\item{\link[=best_practices_linters]{best_practices} (58 linters)} -\item{\link[=common_mistakes_linters]{common_mistakes} (9 linters)} +\item{\link[=best_practices_linters]{best_practices} (59 linters)} +\item{\link[=common_mistakes_linters]{common_mistakes} (10 linters)} \item{\link[=configurable_linters]{configurable} (34 linters)} \item{\link[=consistency_linters]{consistency} (26 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} @@ -105,6 +105,7 @@ The following linters exist: \item{\code{\link{pipe_call_linter}} (tags: readability, style)} \item{\code{\link{pipe_consistency_linter}} (tags: configurable, readability, style)} \item{\code{\link{pipe_continuation_linter}} (tags: default, readability, style)} +\item{\code{\link{pipe_return_linter}} (tags: best_practices, common_mistakes)} \item{\code{\link{print_linter}} (tags: best_practices, consistency)} \item{\code{\link{quotes_linter}} (tags: configurable, consistency, default, readability, style)} \item{\code{\link{redundant_equals_linter}} (tags: best_practices, common_mistakes, efficiency, readability)} diff --git a/man/pipe_return_linter.Rd b/man/pipe_return_linter.Rd new file mode 100644 index 000000000..8527e8ab9 --- /dev/null +++ b/man/pipe_return_linter.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/pipe_return_linter.R +\name{pipe_return_linter} +\alias{pipe_return_linter} +\title{Block usage of return() in magrittr pipelines} +\usage{ +pipe_return_linter() +} +\description{ +\code{\link[=return]{return()}} inside a magrittr pipeline does not actually execute \code{return()} +like you'd expect: \verb{\\(x) \{ x \%>\% return(); FALSE \}} will return \code{FALSE}! +It will technically work "as expected" if this is the final statement +in the function body, but such usage is misleading. Instead, assign +the pipe outcome to a variable and return that. +} +\examples{ +# will produce lints +lint( + text = "function(x) x \%>\% return()", + linters = pipe_return_linter() +) + +# okay +code <- "function(x) {\n y <- sum(x)\n return(y)\n}" +writeLines(code) +lint( + text = code, + linters = pipe_return_linter() +) + +} +\seealso{ +\link{linters} for a complete list of linters available in lintr. +} +\section{Tags}{ +\link[=best_practices_linters]{best_practices}, \link[=common_mistakes_linters]{common_mistakes} +} diff --git a/tests/testthat/test-pipe_return_linter.R b/tests/testthat/test-pipe_return_linter.R new file mode 100644 index 000000000..0c395d48b --- /dev/null +++ b/tests/testthat/test-pipe_return_linter.R @@ -0,0 +1,47 @@ +test_that("pipe_return_linter skips allowed usages", { + linter <- pipe_return_linter() + + normal_pipe_lines <- trim_some(" + x %>% + filter(str > 5) %>% + summarize(str = sum(str)) + ") + expect_lint(normal_pipe_lines, NULL, linter) + + normal_function_lines <- trim_some(" + pipeline <- function(x) { + out <- x %>% + filter(str > 5) %>% + summarize(str = sum(str)) + return(out) + } + ") + expect_lint(normal_function_lines, NULL, linter) + + nested_return_lines <- trim_some(" + pipeline <- function(x) { + x_squared <- x %>% + sapply(function(xi) { + return(xi ** 2) + }) + return(x_squared) + } + ") + expect_lint(nested_return_lines, NULL, linter) +}) + +test_that("pipe_return_linter blocks simple disallowed usages", { + lines <- trim_some(" + pipeline <- function(x) { + out <- x %>% + filter(str > 5) %>% + summarize(str = sum(str)) %>% + return() + } + ") + expect_lint( + lines, + rex::rex("Using return() as the final step of a magrittr pipeline"), + pipe_return_linter() + ) +})