Skip to content

Commit 02b25b1

Browse files
authored
refactor function_left_parentheses_linter() to XPath (#1267)
1 parent 8b3ccc3 commit 02b25b1

File tree

5 files changed

+45
-52
lines changed

5 files changed

+45
-52
lines changed

DESCRIPTION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ Collate:
8585
'extract.R'
8686
'extraction_operator_linter.R'
8787
'fixed_regex_linter.R'
88-
'function_left_parentheses.R'
88+
'function_left_parentheses_linter.R'
8989
'get_source_expressions.R'
9090
'ids_with_token.R'
9191
'ifelse_censor_linter.R'

R/function_left_parentheses.R

Lines changed: 0 additions & 50 deletions
This file was deleted.
Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
#' Function left parentheses linter
2+
#'
3+
#' Check that all left parentheses in a function call do not have spaces before them.
4+
#'
5+
#' @evalRd rd_tags("function_left_parentheses_linter")
6+
#' @seealso
7+
#' [linters] for a complete list of linters available in lintr. \cr
8+
#' <https://style.tidyverse.org/syntax.html#parentheses>
9+
#' @export
10+
function_left_parentheses_linter <- function() { # nolint: object_length.
11+
xpath <- "
12+
//FUNCTION[@col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1] |
13+
//expr[SYMBOL_FUNCTION_CALL and @col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1]
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+
bad_exprs <- xml2::xml_find_all(xml, xpath)
23+
24+
xml_nodes_to_lints(
25+
bad_exprs,
26+
source_expression = source_expression,
27+
lint_message = "Remove spaces before the left parenthesis in a function call.",
28+
range_start_xpath = "number(./@col2 + 1)", # start after function / fun
29+
range_end_xpath = "number(./following-sibling::OP-LEFT-PAREN/@col1 - 1)" # end before (
30+
)
31+
})
32+
}

man/function_left_parentheses_linter.Rd

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

tests/testthat/test-function_left_parentheses_linter.R

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,4 +27,15 @@ test_that("returns the correct linting", {
2727
expect_lint("base::print(blah, f (1))", msg, linter)
2828
expect_lint("`+` (1, 1)", msg, linter)
2929
expect_lint("test <- function (x) { }", msg, linter)
30+
31+
expect_lint(
32+
"blah (1)",
33+
list(message = msg, column_number = 5L, ranges = list(c(5L, 6L))),
34+
linter
35+
)
36+
expect_lint(
37+
"test <- function (x) { }",
38+
list(message = msg, column_number = 17L, ranges = list(c(17L, 18L))),
39+
linter
40+
)
3041
})

0 commit comments

Comments
 (0)