Skip to content

Commit 2040068

Browse files
simplify open_curly_linter using xpath (#1221)
* simplify open_curly_linter using xpath * restore & correct test
1 parent c68c11e commit 2040068

File tree

3 files changed

+125
-86
lines changed

3 files changed

+125
-86
lines changed

R/open_curly_linter.R

+44-53
Original file line numberDiff line numberDiff line change
@@ -10,64 +10,55 @@
1010
#' @export
1111
open_curly_linter <- function(allow_single_line = FALSE) {
1212
lintr_deprecated("open_curly_linter", new = "brace_linter", version = "2.0.1.9001", type = "Linter")
13-
Linter(function(source_expression) {
14-
lapply(
15-
ids_with_token(source_expression, "'{'"),
16-
function(id) {
17-
18-
parsed <- with_id(source_expression, id)
19-
20-
tokens_before <- source_expression$parsed_content$token[
21-
source_expression$parsed_content$line1 == parsed$line1 &
22-
source_expression$parsed_content$col1 < parsed$col1]
23-
24-
tokens_after <- source_expression$parsed_content$token[
25-
source_expression$parsed_content$line1 == parsed$line1 &
26-
source_expression$parsed_content$col1 > parsed$col1 &
27-
source_expression$parsed_content$token != "COMMENT"]
28-
29-
if (isTRUE(allow_single_line) &&
30-
"'}'" %in% tokens_after) {
31-
return()
32-
}
33-
34-
line <- source_expression$lines[as.character(parsed$line1)]
3513

36-
# the only tokens should be the { and the start of the expression.
37-
some_before <- length(tokens_before) %!=% 0L
38-
some_after <- length(tokens_after) %!=% 0L
39-
40-
content_after <- unname(substr(line, parsed$col1 + 1L, nchar(line)))
41-
content_before <- unname(substr(line, 1L, parsed$col1 - 1L))
42-
43-
only_comment <- rex::re_matches(content_after, rex::rex(any_spaces, "#", something, end))
14+
xpath_before <- "//OP-LEFT-BRACE[
15+
not(following-sibling::expr[1][OP-LEFT-BRACE])
16+
and not(parent::expr/preceding-sibling::*[1][OP-LEFT-BRACE])
17+
and @line1 != parent::expr/preceding-sibling::*[1][not(self::ELSE)]/@line2
18+
]"
19+
if (allow_single_line) {
20+
xpath_after <- "//OP-LEFT-BRACE[
21+
not(following-sibling::expr[1][OP-LEFT-BRACE])
22+
and not(parent::expr/preceding-sibling::OP-LEFT-BRACE)
23+
and not(@line2 = following-sibling::OP-RIGHT-BRACE/@line1)
24+
and @line2 = following-sibling::expr[position() = 1 and not(OP-LEFT-BRACE)]/@line1
25+
]"
26+
message_after <- paste(
27+
"Opening curly braces should always be followed by a new line",
28+
"unless the paired closing brace is on the same line."
29+
)
30+
} else {
31+
xpath_after <- "//OP-LEFT-BRACE[
32+
not(following-sibling::expr[1][OP-LEFT-BRACE])
33+
and not(parent::expr/preceding-sibling::OP-LEFT-BRACE)
34+
and @line2 = following-sibling::expr[1]/@line1
35+
]"
36+
message_after <- "Opening curly braces should always be followed by a new line."
37+
}
4438

45-
double_curly <- rex::re_matches(content_after, rex::rex(start, "{")) ||
46-
rex::re_matches(content_before, rex::rex("{", end))
39+
Linter(function(source_expression) {
40+
if (!is_lint_level(source_expression, "expression")) {
41+
return(list())
42+
}
4743

48-
if (double_curly) {
49-
return()
50-
}
44+
xml <- source_expression$xml_parsed_content
5145

52-
whitespace_after <-
53-
unname(substr(line, parsed$col1 + 1L, parsed$col1 + 1L)) %!=% ""
46+
expr_before <- xml2::xml_find_all(xml, xpath_before)
47+
lints_before <- xml_nodes_to_lints(
48+
expr_before,
49+
source_expression = source_expression,
50+
lint_message = "Opening curly braces should never go on their own line.",
51+
type = "style"
52+
)
5453

55-
if (!some_before ||
56-
some_after ||
57-
(whitespace_after && !only_comment)) {
58-
Lint(
59-
filename = source_expression$filename,
60-
line_number = parsed$line1,
61-
column_number = parsed$col1,
62-
type = "style",
63-
message = paste(
64-
"Opening curly braces should never go on their own line and",
65-
"should always be followed by a new line."
66-
),
67-
line = line
68-
)
69-
}
70-
}
54+
expr_after <- xml2::xml_find_all(xml, xpath_after)
55+
lints_after <- xml_nodes_to_lints(
56+
expr_after,
57+
source_expression = source_expression,
58+
lint_message = message_after,
59+
type = "style"
7160
)
61+
62+
return(c(lints_before, lints_after))
7263
})
7364
}

lintr.Rproj

-1
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,5 @@ StripTrailingWhitespace: Yes
1717

1818
BuildType: Package
1919
PackageUseDevtools: Yes
20-
PackageCleanBeforeInstall: Yes
2120
PackageInstallArgs: --no-multiarch --with-keep.source
2221
PackageRoxygenize: rd,collate,namespace
+81-32
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
11
test_that("returns the correct linting", {
2-
msg <- rex("Opening curly braces should never go on their own line and should always be followed by a new line.")
3-
42
expect_warning(
53
linter <- open_curly_linter(),
64
"Linter open_curly_linter was deprecated",
@@ -9,48 +7,99 @@ test_that("returns the correct linting", {
97

108
expect_lint("blah", NULL, linter)
119

12-
expect_lint("a <- function() {\n}", NULL, linter)
13-
1410
expect_lint(
15-
"pkg_name <- function(path = find_package()) {
16-
if (is.null(path)) {
17-
return(NULL)
18-
} else {
19-
read.dcf(file.path(path, \"DESCRIPTION\"), fields = \"Package\")[1]
11+
trim_some("
12+
a <- function() {
2013
}
21-
}", NULL, linter)
14+
"),
15+
NULL,
16+
linter
17+
)
2218

23-
expect_lint("a <- function()\n{\n 1 \n}",
24-
msg,
25-
linter)
19+
expect_lint(
20+
trim_some('
21+
pkg_name <- function(path = find_package()) {
22+
if (is.null(path)) {
23+
return(NULL)
24+
} else {
25+
read.dcf(file.path(path, "DESCRIPTION"), fields = "Package")[1]
26+
}
27+
}
28+
'),
29+
NULL,
30+
linter
31+
)
2632

27-
expect_lint("a <- function()\n {\n 1 \n}",
28-
msg,
29-
linter)
33+
expect_lint(
34+
trim_some("
35+
a <- function()
36+
{
37+
1
38+
}
39+
"),
40+
rex::rex("Opening curly braces should never go on their own line."),
41+
linter
42+
)
3043

31-
expect_lint("a <- function()\n\t{\n 1 \n}",
32-
msg,
33-
linter)
44+
expect_lint(
45+
trim_some("
46+
a <- function()
47+
{
48+
1
49+
}
50+
"),
51+
rex::rex("Opening curly braces should never go on their own line."),
52+
linter
53+
)
3454

35-
expect_lint("a <- function() { \n}",
36-
msg,
37-
linter)
55+
expect_lint(
56+
trim_some("
57+
a <- function()
58+
\t{
59+
1
60+
}
61+
"),
62+
rex::rex("Opening curly braces should never go on their own line"),
63+
linter
64+
)
3865

39-
expect_lint("a <- function() { 1 }",
40-
msg,
41-
linter)
66+
# trailing whitespace _doesn't_ trigger a lint (it used to; leave that to trailing_whitespace_linter now)
67+
expect_lint("a <- function() { \n}", NULL, linter)
4268

43-
expect_lint("a <- function() { 1 }",
44-
NULL,
45-
suppressWarnings(open_curly_linter(allow_single_line = TRUE)))
69+
expect_lint(
70+
"a <- function() { 1 }",
71+
rex::rex("Opening curly braces should always be followed by a new line"),
72+
linter
73+
)
4674

4775
expect_lint(
48-
'if ("P" != "NP") { # what most people expect
49-
print("Cryptomania is possible")
50-
}',
76+
trim_some('
77+
if ("P" != "NP") { # what most people expect
78+
print("Cryptomania is possible")
79+
}
80+
'),
5181
NULL,
52-
linter
82+
linter
5383
)
5484

5585
expect_lint("{{x}}", NULL, linter)
5686
})
87+
88+
test_that("allow_single_line=TRUE works", {
89+
expect_warning(
90+
linter <- open_curly_linter(allow_single_line = TRUE),
91+
"Linter open_curly_linter was deprecated",
92+
fixed = TRUE
93+
)
94+
95+
expect_lint("a <- function() { 1 }", NULL, linter)
96+
97+
expect_lint(
98+
trim_some("
99+
a <- function() { 1
100+
2 }
101+
"),
102+
rex::rex("Opening curly braces should always be followed by a new line unless"),
103+
linter
104+
)
105+
})

0 commit comments

Comments
 (0)