Skip to content

Commit 01fb1e3

Browse files
Merge remote-tracking branch 'origin/unnecessary_nesting' into unnecessary_nesting
2 parents 570ca27 + f4374b1 commit 01fb1e3

File tree

6 files changed

+145
-41
lines changed

6 files changed

+145
-41
lines changed

R/unnecessary_nesting_linter.R

Lines changed: 35 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,13 @@
33
#' Excessive nesting harms readability. Use helper functions or early returns
44
#' to reduce nesting wherever possible.
55
#'
6+
#' @param allow_assignment Logical, default `TRUE`, in which case
7+
#' braced expressions consisting only of a single assignment are skipped.
8+
#' if `FALSE`, all braced expressions with only one child expression are linted.
9+
#' The `TRUE` case facilitates interaction with [implicit_assignment_linter()]
10+
#' for certain cases where an implicit assignment is necessary, so a braced
11+
#' assignment is used to further distinguish the assignment. See examples.
12+
#'
613
#' @examples
714
#' # will produce lints
815
#' code <- "if (A) {\n stop('A is bad!')\n} else {\n do_good()\n}"
@@ -19,6 +26,13 @@
1926
#' linters = unnecessary_nesting_linter()
2027
#' )
2128
#'
29+
#' code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)"
30+
#' writeLines(code)
31+
#' lint(
32+
#' text = code,
33+
#' linters = unnecessary_nesting_linter(allow_assignment = FALSE)
34+
#' )
35+
#'
2236
#' # okay
2337
#' code <- "if (A) {\n stop('A is bad because a.')\n} else {\n stop('!A is bad too.')\n}"
2438
#' writeLines(code)
@@ -34,20 +48,27 @@
3448
#' linters = unnecessary_nesting_linter()
3549
#' )
3650
#'
51+
#' code <- "expect_warning(\n {\n x <- foo()\n },\n 'warned'\n)"
52+
#' writeLines(code)
53+
#' lint(
54+
#' text = code,
55+
#' linters = unnecessary_nesting_linter()
56+
#' )
57+
#'
3758
#' @evalRd rd_tags("unnecessary_nesting_linter")
3859
#' @seealso
3960
#' - [cyclocomp_linter()] for another linter that penalizes overly complexcode.
4061
#' - [linters] for a complete list of linters available in lintr.
4162
#' @export
42-
unnecessary_nesting_linter <- function() {
63+
unnecessary_nesting_linter <- function(allow_assignment = TRUE) {
4364
exit_calls <- c("stop", "return", "abort", "quit", "q")
4465
# These calls can be called in the sibling branch and not trigger a lint,
4566
# allowing for cleanly parallel code, where breaking it would often harm readability:
46-
# if (A) {
47-
# stop()
48-
# } else {
49-
# warning()
50-
# }
67+
# > if (A) {
68+
# > stop()
69+
# > } else {
70+
# > warning()
71+
# > }
5172
# NB: print() is intentionally excluded since its usage is usually a mistake (?print_linter)
5273
signal_calls <- c(
5374
exit_calls,
@@ -93,6 +114,8 @@ unnecessary_nesting_linter <- function() {
93114
]
94115
")
95116

117+
assignment_cond <- if (allow_assignment) "expr[LEFT_ASSIGN or RIGHT_ASSIGN]" else "false"
118+
96119
# several carve-outs of common cases where single-expression braces are OK
97120
# - control flow statements: if, for, while, repeat, switch()
98121
# + switch() is unique in being a function, not a language element
@@ -101,7 +124,7 @@ unnecessary_nesting_linter <- function() {
101124
# + includes purrr-like anonymous functions as ~ {...}
102125
# - rlang's double-brace expressions like {{ var }}
103126
# + NB: both braces would trigger here, so we must exclude both of them
104-
# - any expression ending like `})` or `}]`
127+
# - any expression starting like `({` or `[{` or ending like `})` or `}]`
105128
# + note that nesting is not improved by "fixing" such cases,
106129
# and could also be worsened
107130
# + motivated by the most common cases:
@@ -110,7 +133,7 @@ unnecessary_nesting_linter <- function() {
110133
# * suppressWarnings({ expr })
111134
# * DataTable[, { expr }]
112135
# * DataTable[, col := { expr }] <- requires carve-out for `:=`
113-
unnecessary_brace_xpath <- "
136+
unnecessary_brace_xpath <- glue("
114137
//OP-LEFT-BRACE
115138
/parent::expr[
116139
count(expr) = 1
@@ -128,11 +151,12 @@ unnecessary_nesting_linter <- function() {
128151
and not(expr/OP-LEFT-BRACE)
129152
and not(preceding-sibling::OP-LEFT-BRACE)
130153
and not(
131-
OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-PAREN/@end
132-
or OP-RIGHT-BRACE/@end + 1 = following-sibling::OP-RIGHT-BRACKET/@end
154+
OP-LEFT-BRACE/@end - 1 = preceding-sibling::*[1][self::OP-LEFT-PAREN or self::OP-LEFT-BRACKET]/@end
155+
or OP-RIGHT-BRACE/@end + 1 = following-sibling::*[1][self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACKET]/@end
133156
)
157+
and not({assignment_cond})
134158
]
135-
"
159+
")
136160

137161
Linter(function(source_expression) {
138162
if (!is_lint_level(source_expression, "expression")) {

inst/lintr/linters.csv

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,7 @@ undesirable_operator_linter,style efficiency configurable robustness best_practi
109109
unnecessary_concatenation_linter,style readability efficiency configurable
110110
unnecessary_lambda_linter,best_practices efficiency readability
111111
unnecessary_nested_if_linter,readability best_practices
112-
unnecessary_nesting_linter,readability consistency
112+
unnecessary_nesting_linter,readability consistency configurable
113113
unnecessary_placeholder_linter,readability best_practices
114114
unneeded_concatenation_linter,style readability efficiency configurable deprecated
115115
unreachable_code_linter,best_practices readability

man/configurable_linters.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/linters.Rd

Lines changed: 2 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/unnecessary_nesting_linter.Rd

Lines changed: 24 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-unnecessary_nesting_linter.R

Lines changed: 82 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -224,6 +224,18 @@ test_that("unnecessary_nesting_linter skips one-expression switch statements", {
224224
expect_lint(lines, NULL, unnecessary_nesting_linter())
225225
})
226226

227+
test_that("unnecessary_nesting_linter skips one-expression assignments by default", {
228+
expect_lint(
229+
trim_some("
230+
{
231+
x <- foo()
232+
}
233+
"),
234+
NULL,
235+
unnecessary_nesting_linter()
236+
)
237+
})
238+
227239
test_that("unnecessary_nesting_linter passes for multi-line braced expressions", {
228240
lines <- c(
229241
"tryCatch(",
@@ -240,24 +252,55 @@ test_that("unnecessary_nesting_linter passes for multi-line braced expressions",
240252
test_that("unnecessary_nesting_linter skips if unbracing won't reduce nesting", {
241253
linter <- unnecessary_nesting_linter()
242254

243-
test_that_lines <- c(
244-
"test_that('this works', {",
245-
" expect_true(TRUE)",
246-
"})"
255+
expect_lint(
256+
trim_some("
257+
test_that('this works', {
258+
expect_true(TRUE)
259+
})
260+
"),
261+
NULL,
262+
linter
247263
)
248-
expect_lint(test_that_lines, NULL, linter)
249-
data_table_lines <- c(
250-
"DT[, {",
251-
" plot(x, y)",
252-
"}]"
264+
expect_lint(
265+
trim_some("
266+
DT[, {
267+
plot(x, y)
268+
}]
269+
"),
270+
NULL,
271+
linter
272+
)
273+
expect_lint(
274+
trim_some("
275+
DT[, x := {
276+
foo(x, y)
277+
}]
278+
"),
279+
NULL,
280+
linter
281+
)
282+
283+
# NB: styler would re-style these anyway
284+
expect_lint(
285+
trim_some("
286+
tryCatch({
287+
foo()
288+
}, error = identity)
289+
"),
290+
NULL,
291+
linter
253292
)
254-
expect_lint(data_table_lines, NULL, linter)
255-
data_table_assign_lines <- c(
256-
"DT[, x := {",
257-
" foo(x, y)",
258-
"}]"
293+
294+
expect_lint(
295+
trim_some("
296+
DT[{
297+
n <- .N - 1
298+
x[n] < y[n]
299+
}, j = TRUE, by = x]
300+
"),
301+
NULL,
302+
linter
259303
)
260-
expect_lint(data_table_assign_lines, NULL, linter)
261304
})
262305

263306
test_that("rlang's double-brace operator is skipped", {
@@ -269,17 +312,31 @@ test_that("rlang's double-brace operator is skipped", {
269312
})
270313

271314
test_that("unnecessary_nesting_linter blocks one-expression braced expressions", {
272-
lines <- c(
273-
"tryCatch(",
274-
" {",
275-
" foo(x)",
276-
" },",
277-
" error = identity",
278-
")"
279-
)
280315
expect_lint(
281-
lines,
282-
R"(Reduce the nesting of this statement by removing the braces \{\}\.)",
316+
trim_some("
317+
tryCatch(
318+
{
319+
foo(x)
320+
},
321+
error = identity
322+
)
323+
"),
324+
rex::rex("Reduce the nesting of this statement by removing the braces {}."),
283325
unnecessary_nesting_linter()
284326
)
285327
})
328+
329+
test_that("unnecessary_nesting_linter allow_assignment= argument works", {
330+
expect_lint(
331+
trim_some("
332+
tryCatch(
333+
{
334+
idx <- foo(x)
335+
},
336+
error = identity
337+
)
338+
"),
339+
rex::rex("Reduce the nesting of this statement by removing the braces {}."),
340+
unnecessary_nesting_linter(allow_assignment = FALSE)
341+
)
342+
})

0 commit comments

Comments
 (0)