Skip to content

Commit 1347524

Browse files
Merge branch 'main' into base_overwrite
2 parents 4476ba4 + 7d20334 commit 1347524

File tree

9 files changed

+260
-2
lines changed

9 files changed

+260
-2
lines changed

DESCRIPTION

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,6 +145,7 @@ Collate:
145145
'object_name_linter.R'
146146
'object_overwrite_linter.R'
147147
'object_usage_linter.R'
148+
'one_call_pipe_linter.R'
148149
'outer_negation_linter.R'
149150
'package_hooks_linter.R'
150151
'paren_body_linter.R'

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,7 @@ export(object_length_linter)
107107
export(object_name_linter)
108108
export(object_overwrite_linter)
109109
export(object_usage_linter)
110+
export(one_call_pipe_linter)
110111
export(open_curly_linter)
111112
export(outer_negation_linter)
112113
export(package_hooks_linter)

R/one_call_pipe_linter.R

Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
#' Block single-call magrittr pipes
2+
#'
3+
#' Prefer using a plain call instead of a pipe with only one call,
4+
#' i.e. `1:10 %>% sum()` should instead be `sum(1:10)`. Note that
5+
#' calls in the first `%>%` argument count. `rowSums(x) %>% max()` is OK
6+
#' because there are two total calls (`rowSums()` and `max()`).
7+
#'
8+
#' Note also that un-"called" steps are *not* counted, since they should
9+
#' be calls (see [pipe_call_linter()]).
10+
#'
11+
#' @examples
12+
#' # will produce lints
13+
#' lint(
14+
#' text = "(1:10) %>% sum()",
15+
#' linters = one_call_pipe_linter()
16+
#' )
17+
#'
18+
#' lint(
19+
#' text = "DT %>% .[grp == 'a', sum(v)]",
20+
#' linters = one_call_pipe_linter()
21+
#' )
22+
#'
23+
#' # okay
24+
#' lint(
25+
#' text = "rowSums(x) %>% mean()",
26+
#' linters = one_call_pipe_linter()
27+
#' )
28+
#'
29+
#' lint(
30+
#' text = "DT[src == 'a', .N, by = grp] %>% .[N > 10]",
31+
#' linters = one_call_pipe_linter()
32+
#' )
33+
#'
34+
#' @evalRd rd_tags("one_call_pipe_linter")
35+
#' @seealso
36+
#' - [linters] for a complete list of linters available in lintr.
37+
#' - <https://style.tidyverse.org/pipes.html#short-pipes>
38+
#' @export
39+
one_call_pipe_linter <- function() {
40+
pipes_cond <- xp_text_in_table(magrittr_pipes)
41+
42+
# preceding-sibling::SPECIAL: if there are ever two pipes, don't lint
43+
# OP-LEFT-BRACKET/LBB: accept DT[...] %>% .[...] as a two-call pipe,
44+
# (but not DT %>% .[...])
45+
# parent::expr/SPECIAL: make sure we are at the top of a pipeline
46+
# count(): any call anywhere else in the AST within the pipe expression
47+
xpath <- glue("
48+
(//SPECIAL[{pipes_cond}] | //PIPE)[
49+
not(preceding-sibling::expr[1]/*[self::SPECIAL[{pipes_cond}] or self::PIPE])
50+
and (
51+
not(following-sibling::expr[OP-LEFT-BRACKET or LBB])
52+
or not(preceding-sibling::expr[OP-LEFT-BRACKET or LBB])
53+
)
54+
]
55+
/parent::expr[
56+
not(parent::expr/*[self::SPECIAL[{ pipes_cond }] or self::PIPE])
57+
and count(.//SYMBOL_FUNCTION_CALL) <= 1
58+
]
59+
")
60+
61+
Linter(function(source_expression) {
62+
if (!is_lint_level(source_expression, "expression")) {
63+
return(list())
64+
}
65+
66+
xml <- source_expression$xml_parsed_content
67+
68+
bad_expr <- xml_find_all(xml, xpath)
69+
pipe <- xml_find_chr(bad_expr, "string(SPECIAL | PIPE)")
70+
71+
xml_nodes_to_lints(
72+
bad_expr,
73+
source_expression = source_expression,
74+
lint_message = paste0("Expressions with only a single call shouldn't use pipe ", pipe, "."),
75+
type = "warning"
76+
)
77+
})
78+
}

inst/lintr/linters.csv

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,7 @@ object_length_linter,style readability default configurable executing
6464
object_name_linter,style consistency default configurable executing
6565
object_overwrite_linter,best_practices robustness readability configurable executing
6666
object_usage_linter,style readability correctness default executing configurable
67+
one_call_pipe_linter,style readability
6768
open_curly_linter,defunct
6869
outer_negation_linter,readability efficiency best_practices
6970
package_hooks_linter,style correctness package_development

man/linters.Rd

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

man/one_call_pipe_linter.Rd

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

man/readability_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/style_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.
Lines changed: 123 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,123 @@
1+
test_that("one_call_pipe_linter skips allowed usages", {
2+
linter <- one_call_pipe_linter()
3+
4+
# two pipe steps is OK
5+
expect_lint("x %>% foo() %>% bar()", NULL, linter)
6+
# call in first step --> OK
7+
expect_lint("foo(x) %>% bar()", NULL, linter)
8+
# both calls in second step --> OK
9+
expect_lint("x %>% foo(bar(.))", NULL, linter)
10+
})
11+
12+
test_that("one_call_pipe_linter blocks simple disallowed usages", {
13+
linter <- one_call_pipe_linter()
14+
lint_msg <- rex::rex("Expressions with only a single call shouldn't use pipe %>%.")
15+
16+
expect_lint("x %>% foo()", lint_msg, linter)
17+
18+
# new lines don't matter
19+
expect_lint("x %>%\n foo()", lint_msg, linter)
20+
21+
# catch the "inner" pipe chain, not the "outer" one
22+
# TODO(michaelchirico): actually, this should lint twice -- we're too aggressive
23+
# in counting _all_ nested calls.
24+
expect_lint("x %>% inner_join(y %>% filter(is_treatment))", lint_msg, linter)
25+
})
26+
27+
test_that("one_call_pipe_linter skips data.table chains", {
28+
linter <- one_call_pipe_linter()
29+
lint_msg <- rex::rex("Expressions with only a single call shouldn't use pipe %>%.")
30+
31+
expect_lint("DT[x > 5, sum(y), by = keys] %>% .[, .SD[1], by = key1]", NULL, linter)
32+
33+
# lint here: instead of a pipe, use DT[x > 5, sum(y), by = keys]
34+
expect_lint("DT %>% .[x > 5, sum(y), by = keys]", lint_msg, linter)
35+
36+
# ditto for [[
37+
expect_lint("DT %>% rowSums() %>% .[[idx]]", NULL, linter)
38+
39+
expect_lint("DT %>% .[[idx]]", lint_msg, linter)
40+
})
41+
42+
test_that("one_call_pipe_linter treats all pipes equally", {
43+
linter <- one_call_pipe_linter()
44+
45+
expect_lint("foo %>% bar() %$% col", NULL, linter)
46+
expect_lint(
47+
"x %T>% foo()",
48+
rex::rex("Expressions with only a single call shouldn't use pipe %T>%."),
49+
linter
50+
)
51+
expect_lint(
52+
"x %$%\n foo()",
53+
rex::rex("Expressions with only a single call shouldn't use pipe %$%."),
54+
linter
55+
)
56+
expect_lint(
57+
'data %>% filter(type == "console") %$% obscured_gaia_id %>% unique()',
58+
NULL,
59+
linter
60+
)
61+
})
62+
63+
test_that("multiple lints are generated correctly", {
64+
expect_lint(
65+
trim_some("{
66+
a %>% b()
67+
c %$% d()
68+
e %T>%
69+
f()
70+
}"),
71+
list(
72+
list(rex::rex("pipe %>%"), line_number = 2L),
73+
list(rex::rex("pipe %$%"), line_number = 3L),
74+
list(rex::rex("pipe %T>%"), line_number = 4L)
75+
),
76+
one_call_pipe_linter()
77+
)
78+
})
79+
80+
test_that("Native pipes are handled as well", {
81+
skip_if_not_r_version("4.1.0")
82+
83+
linter <- one_call_pipe_linter()
84+
85+
expect_lint(
86+
"x |> foo()",
87+
rex::rex("Expressions with only a single call shouldn't use pipe |>."),
88+
linter
89+
)
90+
91+
# mixed pipes
92+
expect_lint("x |> foo() %>% bar()", NULL, linter)
93+
expect_lint("x %>% foo() |> bar()", NULL, linter)
94+
95+
expect_lint(
96+
trim_some("{
97+
a %>% b()
98+
c |> d()
99+
}"),
100+
list(
101+
list(message = "pipe %>%"),
102+
list(message = "pipe |>")
103+
),
104+
linter
105+
)
106+
})
107+
108+
test_that("one_call_pipe_linter skips data.table chains with native pipe", {
109+
skip_if_not_r_version("4.3.0")
110+
111+
linter <- one_call_pipe_linter()
112+
lint_msg <- rex::rex("Expressions with only a single call shouldn't use pipe |>.")
113+
114+
expect_lint("DT[x > 5, sum(y), by = keys] |> _[, .SD[1], by = key1]", NULL, linter)
115+
116+
# lint here: instead of a pipe, use DT[x > 5, sum(y), by = keys]
117+
expect_lint("DT |> _[x > 5, sum(y), by = keys]", lint_msg, linter)
118+
119+
# ditto for [[
120+
expect_lint("DT |> rowSums() |> _[[idx]]", NULL, linter)
121+
122+
expect_lint("DT |> _[[idx]]", lint_msg, linter)
123+
})

0 commit comments

Comments
 (0)