-
Notifications
You must be signed in to change notification settings - Fork 186
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
New unnecessary_placeholder_linter (#1656)
* New unnecessary_placeholder_linter * add examples, links * remove TODO (posted as issue comment) Co-authored-by: Indrajeet Patil <[email protected]>
- Loading branch information
1 parent
49f9bee
commit 83ef5b8
Showing
10 changed files
with
147 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,69 @@ | ||
#' Block usage of pipeline placeholders if unnecessary | ||
#' | ||
#' The argument placeholder `.` in magrittr pipelines is unnecessary if | ||
#' passed as the first positional argument; using it can cause confusion | ||
#' and impacts readability. | ||
#' | ||
#' @examples | ||
#' # will produce lints | ||
#' lint( | ||
#' text = "x %>% sum(., na.rm = TRUE)", | ||
#' linters = unnecessary_placeholder_linter() | ||
#' ) | ||
#' | ||
#' # okay | ||
#' lint( | ||
#' text = "x %>% sum(na.rm = TRUE)", | ||
#' linters = unnecessary_placeholder_linter() | ||
#' ) | ||
#' | ||
#' lint( | ||
#' text = "x %>% lm(data = ., y ~ z)", | ||
#' linters = unnecessary_placeholder_linter() | ||
#' ) | ||
#' | ||
#' lint( | ||
#' text = "x %>% outer(., .)", | ||
#' linters = unnecessary_placeholder_linter() | ||
#' ) | ||
#' | ||
#' @evalRd rd_tags("unnecessary_placeholder_linter") | ||
#' @seealso [linters] for a complete list of linters available in lintr. | ||
#' @export | ||
unnecessary_placeholder_linter <- function() { | ||
# TODO(michaelchirico): handle R4.2.0 native placeholder _ as well | ||
xpath <- " | ||
//SPECIAL[text() = '%>%'] | ||
/following-sibling::expr[ | ||
expr/SYMBOL_FUNCTION_CALL | ||
and not(expr[ | ||
position() > 2 | ||
and descendant-or-self::expr/SYMBOL[text() = '.'] | ||
]) | ||
] | ||
/expr[2][ | ||
SYMBOL[text() = '.'] | ||
and not(preceding-sibling::*[1][self::EQ_SUB]) | ||
] | ||
" | ||
|
||
Linter(function(source_expression) { | ||
if (!is_lint_level(source_expression, "expression")) { | ||
return(list()) | ||
} | ||
|
||
xml <- source_expression$xml_parsed_content | ||
|
||
bad_expr <- xml2::xml_find_all(xml, xpath) | ||
|
||
xml_nodes_to_lints( | ||
bad_expr, | ||
source_expression = source_expression, | ||
lint_message = paste( | ||
"Don't use the placeholder (`.`) when it's not needed,", | ||
"i.e., when it's only used as the first positional argument in a pipeline step." | ||
), | ||
type = "warning" | ||
) | ||
}) | ||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,25 @@ | ||
test_that("unnecessary_placeholder_linter skips allowed usages", { | ||
# . used in position other than first --> ok | ||
expect_lint("x %>% foo(y, .)", NULL, unnecessary_placeholder_linter()) | ||
# ditto for nested usage | ||
expect_lint("x %>% foo(y, bar(.))", NULL, unnecessary_placeholder_linter()) | ||
# . used twice --> ok | ||
expect_lint("x %>% foo(., .)", NULL, unnecessary_placeholder_linter()) | ||
# . used as a keyword argument --> ok | ||
expect_lint("x %>% foo(arg = .)", NULL, unnecessary_placeholder_linter()) | ||
}) | ||
|
||
test_that("unnecessary_placeholder_linter blocks simple disallowed usages", { | ||
expect_lint( | ||
"x %>% sum(.)", | ||
rex::rex("Don't use the placeholder (`.`) when it's not needed"), | ||
unnecessary_placeholder_linter() | ||
) | ||
|
||
# can come anywhere in the pipeline | ||
expect_lint( | ||
"x %>% y(.) %>% sum()", | ||
rex::rex("Don't use the placeholder (`.`) when it's not needed"), | ||
unnecessary_placeholder_linter() | ||
) | ||
}) |