Skip to content

Commit 4b3487e

Browse files
New function_return_linter() (#1569)
1 parent 54cb0bf commit 4b3487e

10 files changed

+130
-2
lines changed

DESCRIPTION

+1
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ Collate:
9494
'fixed_regex_linter.R'
9595
'function_argument_linter.R'
9696
'function_left_parentheses_linter.R'
97+
'function_return_linter.R'
9798
'get_source_expressions.R'
9899
'ids_with_token.R'
99100
'ifelse_censor_linter.R'

NAMESPACE

+1
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ export(extraction_operator_linter)
5858
export(fixed_regex_linter)
5959
export(function_argument_linter)
6060
export(function_left_parentheses_linter)
61+
export(function_return_linter)
6162
export(get_r_string)
6263
export(get_source_expressions)
6364
export(ids_with_token)

NEWS.md

+3
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,9 @@
2929
can be `purrr::map(x, quantile, 0.75, na.rm = TRUE)`. Naming `probs = 0.75` can further improve readability.
3030
* `redundant_equals_linter()` for redundant comparisons to `TRUE` or `FALSE` like `is_treatment == TRUE` (#1500, @MichaelChirico)
3131

32+
* `function_return_linter()` for handling issues in function `return()` statements. Currently handles assignments within the `return()`
33+
clause, e.g. `return(x <- foo())` (@MichaelChirico)
34+
3235
# lintr 3.0.1
3336

3437
* Skip multi-byte tests in non UTF-8 locales (#1504)

R/function_return_linter.R

+32
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
#' Lint common mistakes/style issues cropping up from return statements
2+
#'
3+
#' `return(x <- ...)` is either distracting (because `x` is ignored), or
4+
#' confusing (because assigning to `x` has some side effect that is muddled
5+
#' by the dual-purpose expression).
6+
#'
7+
#' @evalRd rd_tags("function_return_linter")
8+
#' @seealso [linters] for a complete list of linters available in lintr.
9+
#' @export
10+
function_return_linter <- function() {
11+
xpath <- "
12+
//SYMBOL_FUNCTION_CALL[text() = 'return']
13+
/parent::expr/parent::expr/expr[LEFT_ASSIGN or RIGHT_ASSIGN]
14+
"
15+
16+
Linter(function(source_expression) {
17+
if (!is_lint_level(source_expression, "expression")) {
18+
return(list())
19+
}
20+
21+
xml <- source_expression$xml_parsed_content
22+
23+
bad_expr <- xml2::xml_find_all(xml, xpath)
24+
25+
xml_nodes_to_lints(
26+
bad_expr,
27+
source_expression = source_expression,
28+
lint_message = "Move the assignment outside of the return() clause, or skip assignment altogether.",
29+
type = "warning"
30+
)
31+
})
32+
}

inst/lintr/linters.csv

+1
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ extraction_operator_linter,style best_practices
2929
fixed_regex_linter,best_practices readability efficiency
3030
function_argument_linter,style consistency best_practices
3131
function_left_parentheses_linter,style readability default
32+
function_return_linter,readability best_practices
3233
ifelse_censor_linter,best_practices efficiency
3334
implicit_integer_linter,style consistency best_practices
3435
infix_spaces_linter,style readability default

man/best_practices_linters.Rd

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/function_return_linter.Rd

+19
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/linters.Rd

+3-2
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/readability_linters.Rd

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,68 @@
1+
test_that("function_return_linter skips allowed usages", {
2+
lines_simple <- trim_some("
3+
foo <- function(x) {
4+
x <- x + 1
5+
return(x)
6+
}
7+
")
8+
expect_lint(lines_simple, NULL, function_return_linter())
9+
10+
# arguably an expression as complicated as this should also be assigned,
11+
# but for now that's out of the scope of this linter
12+
lines_subassignment <- trim_some("
13+
foo <- function(x) {
14+
return(x[, {
15+
col <- col + 1
16+
.(grp, col)
17+
}])
18+
}
19+
")
20+
expect_lint(lines_subassignment, NULL, function_return_linter())
21+
})
22+
23+
test_that("function_return_linter blocks simple disallowed usages", {
24+
linter <- function_return_linter()
25+
lint_msg <- rex::rex("Move the assignment outside of the return() clause")
26+
27+
expect_lint(
28+
trim_some("
29+
foo <- function(x) {
30+
return(x <- x + 1)
31+
}
32+
"),
33+
lint_msg,
34+
linter
35+
)
36+
37+
expect_lint(
38+
trim_some("
39+
foo <- function(x) {
40+
return(x <<- x + 1)
41+
}
42+
"),
43+
lint_msg,
44+
linter
45+
)
46+
47+
expect_lint(
48+
trim_some("
49+
foo <- function(x) {
50+
return(x + 1 -> x)
51+
}
52+
"),
53+
lint_msg,
54+
linter
55+
)
56+
57+
side_effect_lines <-
58+
expect_lint(
59+
trim_some("
60+
e <- new.env()
61+
foo <- function(x) {
62+
return(e$val <- x + 1)
63+
}
64+
"),
65+
lint_msg,
66+
linter
67+
)
68+
})

0 commit comments

Comments
 (0)