Skip to content

Commit

Permalink
Merge cd74f81 into 9920110
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico authored Nov 19, 2023
2 parents 9920110 + cd74f81 commit b5daff7
Show file tree
Hide file tree
Showing 10 changed files with 132 additions and 2 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -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'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
39 changes: 39 additions & 0 deletions R/pipe_return_linter.R
Original file line number Diff line number Diff line change
@@ -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."
)
)
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
1 change: 1 addition & 0 deletions man/best_practices_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/common_mistakes_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 3 additions & 2 deletions man/linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

37 changes: 37 additions & 0 deletions man/pipe_return_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

47 changes: 47 additions & 0 deletions tests/testthat/test-pipe_return_linter.R
Original file line number Diff line number Diff line change
@@ -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()
)
})

0 comments on commit b5daff7

Please sign in to comment.