Skip to content

Commit d0dcff7

Browse files
Merge c09d105 into bb7669a
2 parents bb7669a + c09d105 commit d0dcff7

15 files changed

+82
-42
lines changed

NEWS.md

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,14 @@
88
## New and improved features
99

1010
* `library_call_linter()` can detect if all library calls are not at the top of your script (#2027, @nicholas-masel).
11+
* Several linters avoiding false positives in `$` extractions get the same exceptions for `@` extractions, e.g. `S4@T` will no longer throw a `T_and_F_symbol_linter()` hit (#2039, @MichaelChirico).
12+
+ `T_and_F_symbol_linter()`
13+
+ `for_loop_index_linter()`
14+
+ `literal_coercion_linter()`
15+
+ `object_name_linter()`
16+
+ `undesirable_function_linter()`
17+
+ `unreachable_code_linter()`
18+
+ `yoda_test_linter()`
1119

1220
## Changes to defaults
1321

R/T_and_F_symbol_linter.R

Lines changed: 12 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -31,29 +31,15 @@
3131
#' - <https://style.tidyverse.org/syntax.html#logical-vectors>
3232
#' @export
3333
T_and_F_symbol_linter <- function() { # nolint: object_name.
34-
xpath <- paste0(
35-
"//SYMBOL[",
36-
" (text() = 'T' or text() = 'F')", # T or F symbol
37-
" and not(preceding-sibling::OP-DOLLAR)", # not part of a $-subset expression
38-
" and not(parent::expr[",
39-
" following-sibling::LEFT_ASSIGN", # not target of left assignment
40-
" or preceding-sibling::RIGHT_ASSIGN", # not target of right assignment
41-
" or following-sibling::EQ_ASSIGN", # not target of equals assignment
42-
" ])",
43-
"]"
44-
)
34+
symbol_xpath <- "//SYMBOL[
35+
(text() = 'T' or text() = 'F')
36+
and not(parent::expr[OP-DOLLAR or OP-AT])
37+
]"
38+
assignment_xpath <-
39+
"parent::expr[following-sibling::LEFT_ASSIGN or preceding-sibling::RIGHT_ASSIGN or following-sibling::EQ_ASSIGN]"
4540

46-
xpath_assignment <- paste0(
47-
"//SYMBOL[",
48-
" (text() = 'T' or text() = 'F')", # T or F symbol
49-
" and not(preceding-sibling::OP-DOLLAR)", # not part of a $-subset expression
50-
" and parent::expr[", # , but ...
51-
" following-sibling::LEFT_ASSIGN", # target of left assignment
52-
" or preceding-sibling::RIGHT_ASSIGN", # target of right assignment
53-
" or following-sibling::EQ_ASSIGN", # target of equals assignment
54-
" ]",
55-
"]"
56-
)
41+
usage_xpath <- sprintf("%s[not(%s)]", symbol_xpath, assignment_xpath)
42+
assignment_xpath <- sprintf("%s[%s]", symbol_xpath, assignment_xpath)
5743

5844
replacement_map <- c(T = "TRUE", F = "FALSE")
5945

@@ -62,8 +48,8 @@ T_and_F_symbol_linter <- function() { # nolint: object_name.
6248
return(list())
6349
}
6450

65-
bad_exprs <- xml2::xml_find_all(source_expression$xml_parsed_content, xpath)
66-
bad_assigns <- xml2::xml_find_all(source_expression$xml_parsed_content, xpath_assignment)
51+
bad_usage <- xml2::xml_find_all(source_expression$xml_parsed_content, usage_xpath)
52+
bad_assignment <- xml2::xml_find_all(source_expression$xml_parsed_content, assignment_xpath)
6753

6854
make_lints <- function(expr, fmt) {
6955
symbol <- xml2::xml_text(expr)
@@ -79,8 +65,8 @@ T_and_F_symbol_linter <- function() { # nolint: object_name.
7965
}
8066

8167
c(
82-
make_lints(bad_exprs, "Use %s instead of the symbol %s."),
83-
make_lints(bad_assigns, "Don't use %2$s as a variable name, as it can break code relying on %2$s being %1$s.")
68+
make_lints(bad_usage, "Use %s instead of the symbol %s."),
69+
make_lints(bad_assignment, "Don't use %2$s as a variable name, as it can break code relying on %2$s being %1$s.")
8470
)
8571
})
8672
}

R/for_loop_index_linter.R

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -34,10 +34,7 @@ for_loop_index_linter <- function() {
3434
//forcond
3535
/SYMBOL[text() =
3636
following-sibling::expr
37-
//SYMBOL[not(
38-
preceding-sibling::OP-DOLLAR
39-
or parent::expr[preceding-sibling::OP-LEFT-BRACKET]
40-
)]
37+
//SYMBOL[not(parent::expr[OP-DOLLAR or OP-AT or preceding-sibling::OP-LEFT-BRACKET])]
4138
/text()
4239
]
4340
"

R/literal_coercion_linter.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -54,11 +54,11 @@ literal_coercion_linter <- function() {
5454

5555
# notes for clarification:
5656
# - as.integer(1e6) is arguably easier to read than 1000000L
57-
# - in x$"abc", the "abc" STR_CONST is at the top level, so exclude OP-DOLLAR
57+
# - in x$"abc", the "abc" STR_CONST is at the top level, so exclude OP-DOLLAR (ditto OP-AT)
5858
# - need condition against STR_CONST w/ EQ_SUB to skip quoted keyword arguments (see tests)
5959
# - for {rlang} coercers, both `int(1)` and `int(1, )` need to be linted
6060
not_extraction_or_scientific <- "
61-
not(OP-DOLLAR)
61+
not(OP-DOLLAR or OP-AT)
6262
and (
6363
NUM_CONST[not(contains(translate(text(), 'E', 'e'), 'e'))]
6464
or STR_CONST[not(following-sibling::*[1][self::EQ_SUB])]

R/object_name_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ object_name_xpath <- local({
1010
# is not possible for strings, though we do still have to
1111
# be aware of cases like 'a$"b" <- 1'.
1212
xp_assignment_target_fmt <- paste0(
13-
"not(preceding-sibling::OP-DOLLAR)",
13+
"not(parent::expr[OP-DOLLAR or OP-AT])",
1414
"and %1$s::expr[",
1515
" following-sibling::LEFT_ASSIGN",
1616
" or preceding-sibling::RIGHT_ASSIGN",

R/undesirable_function_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ undesirable_function_linter <- function(fun = default_undesirable_functions,
6969
xp_text_in_table(c("library", "require")),
7070
"]])"
7171
),
72-
"not(preceding-sibling::OP-DOLLAR)"
72+
"not(parent::expr[OP-DOLLAR or OP-AT])"
7373
)
7474

7575
if (symbol_is_undesirable) {

R/unreachable_code_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ unreachable_code_linter <- function() {
3737
/following-sibling::expr
3838
/*[
3939
self::expr
40-
and expr[1][not(OP-DOLLAR) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]
40+
and expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]
4141
and (position() != last() - 1 or not(following-sibling::OP-RIGHT-BRACE))
4242
and @line2 < following-sibling::*[1]/@line2
4343
]

R/yoda_test_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ yoda_test_linter <- function() {
4242
# TODO(#963): fully generalize this & re-use elsewhere
4343
const_condition <- "
4444
NUM_CONST
45-
or (STR_CONST and not(OP-DOLLAR))
45+
or (STR_CONST and not(OP-DOLLAR or OP-AT))
4646
or ((OP-PLUS or OP-MINUS) and count(expr[NUM_CONST]) = 2)
4747
"
4848
xpath <- glue::glue("

tests/testthat/test-T_and_F_symbol_linter.R

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,10 @@ test_that("T_and_F_symbol_linter blocks disallowed usages", {
2626
linter
2727
)
2828

29+
expect_lint("DF$bool <- T", msg_true, linter)
30+
expect_lint("S4@bool <- T", msg_true, linter)
31+
expect_lint("sum(x, na.rm = T)", msg_true, linter)
32+
2933
# Regression test for #657
3034
expect_lint(
3135
trim_some("
@@ -35,15 +39,16 @@ test_that("T_and_F_symbol_linter blocks disallowed usages", {
3539
)
3640
3741
x$F <- 42L
42+
y@T <- 84L
3843
3944
T <- \"foo\"
4045
F = \"foo2\"
4146
\"foo3\" -> T
4247
"),
4348
list(
44-
list(message = msg_variable_true),
45-
list(message = msg_variable_false),
46-
list(message = msg_variable_true)
49+
list(message = msg_variable_true, line_number = 9L),
50+
list(message = msg_variable_false, line_number = 10L),
51+
list(message = msg_variable_true, line_number = 11L)
4752
),
4853
linter
4954
)

tests/testthat/test-for_loop_index_linter.R

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,22 @@ test_that("for_loop_index_linter skips allowed usages", {
55

66
# this is OK, so not every symbol is problematic
77
expect_lint("for (col in DF$col) {}", NULL, linter)
8+
expect_lint("for (col in S4@col) {}", NULL, linter)
89
expect_lint("for (col in DT[, col]) {}", NULL, linter)
10+
11+
# make sure symbol check is scoped
12+
expect_lint(
13+
trim_some("
14+
{
15+
for (i in 1:10) {
16+
42L
17+
}
18+
i <- 7L
19+
}
20+
"),
21+
NULL,
22+
linter
23+
)
924
})
1025

1126
test_that("for_loop_index_linter blocks simple disallowed usages", {

0 commit comments

Comments
 (0)