Skip to content

Commit c8f0074

Browse files
finer-tuned handling of ambiguous XML nodes for infix operators (#2115)
* finer-tuned handling of ambiguous XML nodes for infix operators * tidy * adjust NEWS * extra newline * centralize exact tag match logic * shrink diff * simplify undesirable operator case --------- Co-authored-by: AshesITR <[email protected]>
1 parent dd445d8 commit c8f0074

File tree

6 files changed

+40
-40
lines changed

6 files changed

+40
-40
lines changed

NEWS.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
# lintr (development version)
22

3+
## Breaking changes
4+
5+
* `infix_spaces_linter()` distinguishes `<-`, `:=`, `<<-` and `->`, `->>`, i.e. `infix_spaces_linter(exclude_operators = "->")` will no longer exclude `->>` (#2115, @MichaelChirico). This change is breaking for users relying on manually-supplied `exclude_operators` containing `"<-"` to also exclude `:=` and `<<-`. The fix is to manually supply `":="` and `"<<-"` as well. We don't expect this change to affect many users, the fix is simple, and the new behavior is much more transparent, so we are including this breakage in a minor release.
6+
37
## Bug fixes
48

59
* `inner_combine_linter()` no longer throws on length-1 calls to `c()` like `c(exp(2))` or `c(log(3))` (#2017, @MichaelChirico). Such usage is discouraged by `unnecessary_concatenation_linter()`, but `inner_combine_linter()` _per se_ does not apply.

R/infix_spaces_linter.R

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,9 +6,8 @@
66
#' @param exclude_operators Character vector of operators to exclude from consideration for linting.
77
#' Default is to include the following "low-precedence" operators:
88
#' `+`, `-`, `~`, `>`, `>=`, `<`, `<=`, `==`, `!=`, `&`, `&&`, `|`, `||`, `<-`, `:=`, `<<-`, `->`, `->>`,
9-
#' `=`, `/`, `*`, and any infix operator (exclude infixes by passing `"%%"`). Note that `<-`, `:=`, and `<<-`
10-
#' are included/excluded as a group (indicated by passing `"<-"`), as are `->` and `->>` (_viz_, `"->"`),
11-
#' and that `=` for assignment and for setting arguments in calls are treated the same.
9+
#' `=`, `/`, `*`, and any infix operator (exclude infixes by passing `"%%"`). Note that `=` for assignment
10+
#' and for setting arguments in calls are treated the same.
1211
#' @param allow_multiple_spaces Logical, default `TRUE`. If `FALSE`, usage like `x = 2` will also be linted;
1312
#' excluded by default because such usage can sometimes be used for better code alignment, as is allowed
1413
#' by the style guide.
@@ -65,9 +64,8 @@ infix_spaces_linter <- function(exclude_operators = NULL, allow_multiple_spaces
6564
lint_message <- "Put exactly one space on each side of infix operators."
6665
}
6766

68-
infix_tokens <- infix_metadata[
69-
infix_metadata$low_precedence & !infix_metadata$string_value %in% exclude_operators,
70-
"xml_tag"
67+
infix_tokens <- infix_metadata$xml_tag_exact[
68+
infix_metadata$low_precedence & !infix_metadata$string_value %in% exclude_operators
7169
]
7270

7371
# NB: preceding-sibling::* and not preceding-sibling::expr because

R/shared_constants.R

Lines changed: 16 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -130,8 +130,11 @@ infix_metadata <- data.frame(stringsAsFactors = FALSE, matrix(byrow = TRUE, ncol
130130
"OR", "|",
131131
"AND2", "&&",
132132
"OR2", "||",
133-
"LEFT_ASSIGN", "<-", # also includes := and <<-
134-
"RIGHT_ASSIGN", "->", # also includes ->>
133+
"LEFT_ASSIGN", "<-",
134+
"LEFT_ASSIGN", ":=",
135+
"LEFT_ASSIGN", "<<-",
136+
"RIGHT_ASSIGN", "->",
137+
"RIGHT_ASSIGN", "->>",
135138
"EQ_ASSIGN", "=",
136139
"EQ_SUB", "=", # in calls: foo(x = 1)
137140
"EQ_FORMALS", "=", # in definitions: function(x = 1)
@@ -140,7 +143,8 @@ infix_metadata <- data.frame(stringsAsFactors = FALSE, matrix(byrow = TRUE, ncol
140143
"OP-SLASH", "/",
141144
"OP-STAR", "*",
142145
"OP-COMMA", ",",
143-
"OP-CARET", "^", # also includes **
146+
"OP-CARET", "^",
147+
"OP-CARET", "**",
144148
"OP-AT", "@",
145149
"OP-EXCLAMATION", "!",
146150
"OP-COLON", ":",
@@ -168,16 +172,19 @@ infix_metadata$unary <- infix_metadata$xml_tag %in% c("OP-PLUS", "OP-MINUS", "OP
168172
# high-precedence operators are ignored by this linter; see
169173
# https://style.tidyverse.org/syntax.html#infix-operators
170174
infix_metadata$low_precedence <- infix_metadata$string_value %in% c(
171-
"+", "-", "~", ">", ">=", "<", "<=", "==", "!=", "&", "&&", "|", "||", "<-", "->", "=", "%%", "/", "*", "|>"
175+
"+", "-", "~", ">", ">=", "<", "<=", "==", "!=", "&", "&&", "|", "||",
176+
"<-", ":=", "<<-", "->", "->>", "=", "%%", "/", "*", "|>"
172177
)
173178
# comparators come up in several lints
174179
infix_metadata$comparator <- infix_metadata$string_value %in% c("<", "<=", ">", ">=", "==", "!=")
175180

176-
# undesirable_operator_linter needs to distinguish
177-
infix_overload <- data.frame(
178-
exact_string_value = c("<-", "<<-", "=", "->", "->>", "^", "**"),
179-
xml_tag = rep(c("LEFT_ASSIGN", "RIGHT_ASSIGN", "OP-CARET"), c(3L, 2L, 2L)),
180-
stringsAsFactors = FALSE
181+
# these XML nodes require checking the text() to disambiguate multiple operators using the same tag
182+
infix_metadata$ambiguous_tag <- infix_metadata$xml_tag %in% infix_metadata$xml_tag[duplicated(infix_metadata$xml_tag)]
183+
infix_metadata$xml_tag_exact <- infix_metadata$xml_tag
184+
infix_metadata$xml_tag_exact[infix_metadata$ambiguous_tag] <- sprintf(
185+
"%s[text() = '%s']",
186+
infix_metadata$xml_tag_exact[infix_metadata$ambiguous_tag],
187+
infix_metadata$string_value[infix_metadata$ambiguous_tag]
181188
)
182189

183190
# functions equivalent to base::ifelse() for linting purposes

R/undesirable_operator_linter.R

Lines changed: 5 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -46,24 +46,11 @@ undesirable_operator_linter <- function(op = default_undesirable_operators) {
4646
if (is.null(names(op)) || !all(nzchar(names(op))) || length(op) == 0L) {
4747
stop("'op' should be a non-empty named character vector; use missing elements to indicate default messages.")
4848
}
49-
undesirable_operator_metadata <- merge(
50-
# infix must be handled individually below; non-assignment `=` are always OK
51-
infix_metadata[
52-
infix_metadata$string_value != "%%" & !infix_metadata$xml_tag %in% c("EQ_SUB", "EQ_FORMALS"),
53-
],
54-
infix_overload,
55-
by = "xml_tag", all.x = TRUE
56-
)
57-
58-
included_operators <- undesirable_operator_metadata$string_value %in% names(op) |
59-
undesirable_operator_metadata$exact_string_value %in% names(op)
60-
operator_nodes <- undesirable_operator_metadata$xml_tag[included_operators]
61-
needs_exact_string <- !is.na(undesirable_operator_metadata$exact_string_value[included_operators])
62-
operator_nodes[needs_exact_string] <- sprintf(
63-
"%s[text() = '%s']",
64-
operator_nodes[needs_exact_string],
65-
undesirable_operator_metadata$exact_string_value[included_operators][needs_exact_string]
66-
)
49+
# infix must be handled individually below; non-assignment `=` are always OK
50+
operator_nodes <- infix_metadata$xml_tag_exact[
51+
infix_metadata$string_value %in% setdiff(names(op), "%%") &
52+
!infix_metadata$xml_tag %in% c("EQ_SUB", "EQ_FORMALS")
53+
]
6754

6855
is_infix <- startsWith(names(op), "%")
6956
if (any(is_infix)) {

man/infix_spaces_linter.Rd

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

tests/testthat/test-infix_spaces_linter.R

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,8 @@ test_that("The three `=` are all linted", {
7070
})
7171

7272
test_that("exclude_operators works", {
73+
lint_msg <- rex::rex("Put spaces around all infix operators.")
74+
7375
expect_lint("a+b", NULL, infix_spaces_linter(exclude_operators = "+"))
7476
expect_lint(
7577
trim_some("
@@ -80,10 +82,13 @@ test_that("exclude_operators works", {
8082
infix_spaces_linter(exclude_operators = c("+", "-"))
8183
)
8284

83-
# grouped operators
84-
expect_lint("a<<-1", NULL, infix_spaces_linter(exclude_operators = "<-"))
85-
expect_lint("a:=1", NULL, infix_spaces_linter(exclude_operators = "<-"))
86-
expect_lint("a->>1", NULL, infix_spaces_linter(exclude_operators = "->"))
85+
# operators match on text, not hidden node
86+
expect_lint("a<<-1", lint_msg, infix_spaces_linter(exclude_operators = "<-"))
87+
expect_lint("a<<-1", NULL, infix_spaces_linter(exclude_operators = "<<-"))
88+
expect_lint("a:=1", lint_msg, infix_spaces_linter(exclude_operators = "<-"))
89+
expect_lint("a:=1", NULL, infix_spaces_linter(exclude_operators = ":="))
90+
expect_lint("a->>1", lint_msg, infix_spaces_linter(exclude_operators = "->"))
91+
expect_lint("a->>1", NULL, infix_spaces_linter(exclude_operators = "->>"))
8792
expect_lint("a%any%1", NULL, infix_spaces_linter(exclude_operators = "%%"))
8893
expect_lint("function(a=1) { }", NULL, infix_spaces_linter(exclude_operators = "="))
8994
expect_lint("foo(a=1)", NULL, infix_spaces_linter(exclude_operators = "="))

0 commit comments

Comments
 (0)