Skip to content

Commit

Permalink
review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
AshesITR committed Dec 12, 2023
1 parent fdc8b41 commit d874444
Show file tree
Hide file tree
Showing 39 changed files with 114 additions and 64 deletions.
3 changes: 2 additions & 1 deletion R/any_duplicated_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,8 +86,9 @@ any_duplicated_linter <- function() {

Linter(linter_level = "expression", function(source_expression) {
xml <- source_expression$xml_parsed_content
xml_calls <- source_expression$xml_find_function_calls("any")

any_duplicated_expr <- xml_find_all(source_expression$xml_find_function_calls("any"), any_duplicated_xpath)
any_duplicated_expr <- xml_find_all(xml_calls, any_duplicated_xpath)
any_duplicated_lints <- xml_nodes_to_lints(
any_duplicated_expr,
source_expression = source_expression,
Expand Down
3 changes: 2 additions & 1 deletion R/any_is_na_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,8 @@ any_is_na_linter <- function() {
"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("any"), xpath)
xml_calls <- source_expression$xml_find_function_calls("any")
bad_expr <- xml_find_all(xml_calls, xpath)

xml_nodes_to_lints(
bad_expr,
Expand Down
14 changes: 8 additions & 6 deletions R/boolean_arithmetic_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,28 +35,30 @@ boolean_arithmetic_linter <- function() {
zero_expr <- "(EQ or NE or GT or LE) and expr[NUM_CONST[text() = '0' or text() = '0L']]"
one_expr <- "(LT or GE) and expr[NUM_CONST[text() = '1' or text() = '1L']]"
length_xpath <- glue("
self::SYMBOL_FUNCTION_CALL[text() = 'which' or text() = 'grep']
/parent::expr
parent::expr
/parent::expr
/parent::expr[
expr[SYMBOL_FUNCTION_CALL[text() = 'length']]
and parent::expr[ ({zero_expr}) or ({one_expr})]
]
")
sum_xpath <- glue("
self::SYMBOL_FUNCTION_CALL[text() = 'sum']
/parent::expr
parent::expr
/parent::expr[
expr[
expr[SYMBOL_FUNCTION_CALL[text() = 'grepl']]
or (EQ or NE or GT or LT or GE or LE)
] and parent::expr[ ({zero_expr}) or ({one_expr})]
]
")
any_xpath <- paste(length_xpath, "|", sum_xpath)

Linter(linter_level = "expression", function(source_expression) {
any_expr <- xml_find_all(source_expression$xml_find_function_calls(c("which", "grep", "sum")), any_xpath)
length_calls <- source_expression$xml_find_function_calls(c("which", "grep"))
sum_calls <- source_expression$xml_find_function_calls("sum")
any_expr <- c(
xml_find_all(length_calls, length_xpath),
xml_find_all(sum_calls, sum_xpath)
)

xml_nodes_to_lints(
any_expr,
Expand Down
3 changes: 2 additions & 1 deletion R/class_equals_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,8 @@ class_equals_linter <- function() {
"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("class"), xpath)
xml_calls <- source_expression$xml_find_function_calls("class")
bad_expr <- xml_find_all(xml_calls, xpath)

Check warning on line 48 in R/class_equals_linter.R

View workflow job for this annotation

GitHub Actions / lint

file=R/class_equals_linter.R,line=48,col=0,[indentation_linter] Indentation should be 4 spaces but is 0 spaces.

operator <- xml_find_chr(bad_expr, "string(*[2])")
lint_message <- sprintf(
Expand Down
3 changes: 2 additions & 1 deletion R/condition_call_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,8 @@ condition_call_linter <- function(display_call = FALSE) {
xpath <- glue::glue("parent::expr[{call_cond}]/parent::expr")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("stop", "warning")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("stop", "warning"))
bad_expr <- xml_find_all(xml_calls, xpath)

xml_nodes_to_lints(
bad_expr,
Expand Down
3 changes: 2 additions & 1 deletion R/condition_message_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,8 @@ condition_message_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(translators), xpath)
xml_calls <- source_expression$xml_find_function_calls(translators)
bad_expr <- xml_find_all(xml_calls, xpath)
sep_value <- get_r_string(bad_expr, xpath = "./expr/SYMBOL_SUB[text() = 'sep']/following-sibling::expr/STR_CONST")

bad_expr <- bad_expr[is.na(sep_value) | sep_value %in% c("", " ")]
Expand Down
3 changes: 2 additions & 1 deletion R/conjunct_test_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,8 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE,
)

if (allow_filter != "always") {
filter_expr <- xml_find_all(source_expression$xml_find_function_calls("filter"), filter_xpath)
xml_calls <- source_expression$xml_find_function_calls("filter")
filter_expr <- xml_find_all(xml_calls, filter_xpath)

Check warning on line 147 in R/conjunct_test_linter.R

View workflow job for this annotation

GitHub Actions / lint

file=R/conjunct_test_linter.R,line=147,col=0,[indentation_linter] Indentation should be 6 spaces but is 0 spaces.

filter_lints <- xml_nodes_to_lints(
filter_expr,
Expand Down
3 changes: 2 additions & 1 deletion R/consecutive_assertion_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,8 @@ consecutive_assertion_linter <- function() {

Linter(linter_level = "file", function(source_expression) {
# need the full file to also catch usages at the top level
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("stopifnot", "assert_that")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("stopifnot", "assert_that"))
bad_expr <- xml_find_all(xml_calls, xpath)

matched_function <- xp_call_name(bad_expr)
xml_nodes_to_lints(
Expand Down
3 changes: 2 additions & 1 deletion R/expect_comparison_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,8 @@ expect_comparison_linter <- function() {
)

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("expect_true"), xpath)
xml_calls <- source_expression$xml_find_function_calls("expect_true")
bad_expr <- xml_find_all(xml_calls, xpath)

comparator <- xml_find_chr(bad_expr, "string(expr[2]/*[2])")
expectation <- comparator_expectation_map[comparator]
Expand Down
16 changes: 9 additions & 7 deletions R/expect_identical_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,8 +61,7 @@ expect_identical_linter <- function() {
# where a numeric constant indicates inexact testing is preferable
# - skip calls using dots (`...`); see tests
expect_equal_xpath <- "
self::SYMBOL_FUNCTION_CALL[text() = 'expect_equal']
/parent::expr[not(
parent::expr[not(
following-sibling::EQ_SUB
or following-sibling::expr[
expr[1][SYMBOL_FUNCTION_CALL[text() = 'c']]
Expand All @@ -74,15 +73,18 @@ expect_identical_linter <- function() {
/parent::expr
"
expect_true_xpath <- "
self::SYMBOL_FUNCTION_CALL[text() = 'expect_true']
/parent::expr
parent::expr
/following-sibling::expr[1][expr[1]/SYMBOL_FUNCTION_CALL[text() = 'identical']]
/parent::expr
"
xpath <- paste(expect_equal_xpath, "|", expect_true_xpath)

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("expect_equal", "expect_true")), xpath)
expect_equal_calls <- source_expression$xml_find_function_calls("expect_equal")
expect_true_calls <- source_expression$xml_find_function_calls("expect_true")
bad_expr <- c(
xml_find_all(expect_equal_calls, expect_equal_xpath),
xml_find_all(expect_true_calls, expect_true_xpath)
)

xml_nodes_to_lints(
bad_expr,
source_expression = source_expression,
Expand Down
3 changes: 2 additions & 1 deletion R/expect_length_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,8 @@ expect_length_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("expect_equal", "expect_identical")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
bad_expr <- xml_find_all(xml_calls, xpath)

matched_function <- xp_call_name(bad_expr)
lint_message <- sprintf("expect_length(x, n) is better than %s(length(x), n)", matched_function)
Expand Down
3 changes: 2 additions & 1 deletion R/expect_named_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@ expect_named_linter <- function() {
"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("expect_equal", "expect_identical")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
bad_expr <- xml_find_all(xml_calls, xpath)
matched_function <- xp_call_name(bad_expr)
lint_message <- sprintf("expect_named(x, n) is better than %s(names(x), n)", matched_function)

Expand Down
4 changes: 3 additions & 1 deletion R/expect_s4_class_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,9 @@ expect_s4_class_linter <- function() {
# TODO(michaelchirico): also catch expect_{equal,identical}(methods::is(x), k).
# this seems empirically rare, but didn't check many S4-heavy packages.

bad_expr <- xml_find_all(source_expression$xml_find_function_calls("expect_true"), xpath)
xml_calls <- source_expression$xml_find_function_calls("expect_true")
bad_expr <- xml_find_all(xml_calls, xpath)

xml_nodes_to_lints(
bad_expr,
source_expression = source_expression,
Expand Down
3 changes: 2 additions & 1 deletion R/expect_true_false_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,8 @@ expect_true_false_linter <- function() {
"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("expect_equal", "expect_identical")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("expect_equal", "expect_identical"))
bad_expr <- xml_find_all(xml_calls, xpath)

# NB: use expr/$node, not expr[$node], to exclude other things (especially ns:: parts of the call)
call_name <- xp_call_name(bad_expr, condition = "starts-with(text(), 'expect_')")
Expand Down
19 changes: 12 additions & 7 deletions R/fixed_regex_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -105,9 +105,8 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {

# NB: strsplit doesn't have an ignore.case argument
# NB: we intentionally exclude cases like gsub(x, c("a" = "b")), where "b" is fixed
xpath <- glue("
self::SYMBOL_FUNCTION_CALL[ {xp_text_in_table(pos_1_regex_funs)} ]
/parent::expr[
pos_1_xpath <- glue("
parent::expr[
not(following-sibling::SYMBOL_SUB[
(text() = 'fixed' or text() = 'ignore.case')
and following-sibling::expr[1][NUM_CONST[text() = 'TRUE'] or SYMBOL[text() = 'T']]
Expand All @@ -124,9 +123,9 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {
and preceding-sibling::*[2][self::SYMBOL_SUB/text() = 'pattern']
)
]
|
self::SYMBOL_FUNCTION_CALL[ {xp_text_in_table(pos_2_regex_funs)} ]
/parent::expr[
")
pos_2_xpath <- glue("
parent::expr[
not(following-sibling::SYMBOL_SUB[
text() = 'fixed'
and following-sibling::expr[1][NUM_CONST[text() = 'TRUE'] or SYMBOL[text() = 'T']]
Expand All @@ -140,7 +139,13 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {
")

Linter(linter_level = "expression", function(source_expression) {
patterns <- xml_find_all(source_expression$xml_find_function_calls(c(pos_1_regex_funs, pos_2_regex_funs)), xpath)
pos_1_calls <- source_expression$xml_find_function_calls(pos_1_regex_funs)
pos_2_calls <- source_expression$xml_find_function_calls(pos_2_regex_funs)
patterns <- c(
xml_find_all(pos_1_calls, pos_1_xpath),
xml_find_all(pos_2_calls, pos_2_xpath)
)
class(patterns) <- "xml_nodeset"
pattern_strings <- get_r_string(patterns)

is_static <- is_not_regex(pattern_strings, allow_unescaped)
Expand Down
3 changes: 2 additions & 1 deletion R/if_not_else_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,7 @@ if_not_else_linter <- function(exceptions = c("is.null", "is.na", "missing")) {

Linter(linter_level = "expression", function(source_expression) {
xml <- source_expression$xml_parsed_content
ifelse_calls <- source_expression$xml_find_function_calls(ifelse_funs)

if_expr <- xml_find_all(xml, if_xpath)
if_lints <- xml_nodes_to_lints(
Expand All @@ -93,7 +94,7 @@ if_not_else_linter <- function(exceptions = c("is.null", "is.na", "missing")) {
type = "warning"
)

ifelse_expr <- xml_find_all(source_expression$xml_find_function_calls(ifelse_funs), ifelse_xpath)
ifelse_expr <- xml_find_all(ifelse_calls, ifelse_xpath)
ifelse_call <- xp_call_name(ifelse_expr)
ifelse_lints <- xml_nodes_to_lints(
ifelse_expr,
Expand Down
3 changes: 2 additions & 1 deletion R/ifelse_censor_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,8 @@ ifelse_censor_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(ifelse_funs), xpath)
ifelse_calls <- source_expression$xml_find_function_calls(ifelse_funs)
bad_expr <- xml_find_all(ifelse_calls, xpath)

matched_call <- xp_call_name(bad_expr)
operator <- xml_find_chr(bad_expr, "string(expr[2]/*[2])")
Expand Down
3 changes: 2 additions & 1 deletion R/inner_combine_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,8 @@ inner_combine_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("c"), xpath)
xml_calls <- source_expression$xml_find_function_calls("c")
bad_expr <- xml_find_all(xml_calls, xpath)

matched_call <- xp_call_name(bad_expr, depth = 2L)
lint_message <- paste(
Expand Down
3 changes: 2 additions & 1 deletion R/keyword_quote_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -95,8 +95,9 @@ keyword_quote_linter <- function() {

Linter(linter_level = "expression", function(source_expression) {
xml <- source_expression$xml_parsed_content
xml_calls <- source_expression$xml_find_function_calls(NULL)

call_arg_expr <- xml_find_all(source_expression$xml_find_function_calls(NULL), call_arg_xpath)
call_arg_expr <- xml_find_all(xml_calls, call_arg_xpath)

invalid_call_quoting <- is_valid_r_name(get_r_string(call_arg_expr))

Expand Down
4 changes: 3 additions & 1 deletion R/length_test_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,9 @@ length_test_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("length"), xpath)
xml_calls <- source_expression$xml_find_function_calls("length")
bad_expr <- xml_find_all(xml_calls, xpath)

expr_parts <- vapply(lapply(bad_expr, xml_find_all, "expr[2]/*"), xml_text, character(3L))
lint_message <- sprintf(
"Checking the length of a logical vector is likely a mistake. Did you mean `length(%s) %s %s`?",
Expand Down
3 changes: 2 additions & 1 deletion R/list_comparison_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,8 @@ list_comparison_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(names(list_mapper_alternatives)), xpath)
xml_calls <- source_expression$xml_find_function_calls(names(list_mapper_alternatives))
bad_expr <- xml_find_all(xml_calls, xpath)

list_mapper <- xp_call_name(bad_expr, depth = 2L)

Expand Down
3 changes: 2 additions & 1 deletion R/literal_coercion_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,8 @@ literal_coercion_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(coercers), xpath)
xml_calls <- source_expression$xml_find_function_calls(coercers)
bad_expr <- xml_find_all(xml_calls, xpath)

coercer <- xp_call_name(bad_expr)
# tiptoe around the fact that we don't require {rlang}
Expand Down
3 changes: 2 additions & 1 deletion R/matrix_apply_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,8 @@ matrix_apply_linter <- function() {
fun_xpath <- "expr[position() = 4]"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("apply"), xpath)
xml_calls <- source_expression$xml_find_function_calls("apply")
bad_expr <- xml_find_all(xml_calls, xpath)

variable <- xml_text(xml_find_all(bad_expr, variable_xpath))

Expand Down
3 changes: 2 additions & 1 deletion R/nested_ifelse_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,8 @@ nested_ifelse_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(ifelse_funs), xpath)
xml_calls <- source_expression$xml_find_function_calls(ifelse_funs)
bad_expr <- xml_find_all(xml_calls, xpath)

matched_call <- xp_call_name(bad_expr)
lint_message <- paste(
Expand Down
3 changes: 2 additions & 1 deletion R/nzchar_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -107,7 +107,8 @@ nzchar_linter <- function() {
type = "warning"
)

nchar_expr <- xml_find_all(source_expression$xml_find_function_calls("nchar"), nchar_xpath)
xml_calls <- source_expression$xml_find_function_calls("nchar")
nchar_expr <- xml_find_all(xml_calls, nchar_xpath)
nchar_lints <- xml_nodes_to_lints(
nchar_expr,
source_expression = source_expression,
Expand Down
3 changes: 2 additions & 1 deletion R/outer_negation_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,8 @@ outer_negation_linter <- function() {
"

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls(c("any", "all")), xpath)
xml_calls <- source_expression$xml_find_function_calls(c("any", "all"))
bad_expr <- xml_find_all(xml_calls, xpath)

matched_call <- xp_call_name(bad_expr)
inverse_call <- ifelse(matched_call == "any", "all", "any")
Expand Down
6 changes: 4 additions & 2 deletions R/regex_subset_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,8 @@ regex_subset_linter <- function() {
stringr_xpath <- glue(xpath_fmt, arg_pos = 2L)

Linter(linter_level = "expression", function(source_expression) {
grep_expr <- xml_find_all(source_expression$xml_find_function_calls(c("grepl", "grep")), grep_xpath)
grep_calls <- source_expression$xml_find_function_calls(c("grepl", "grep"))
grep_expr <- xml_find_all(grep_calls, grep_xpath)

grep_lints <- xml_nodes_to_lints(
grep_expr,
Expand All @@ -77,7 +78,8 @@ regex_subset_linter <- function() {
type = "warning"
)

stringr_expr <- xml_find_all(source_expression$xml_find_function_calls(c("str_detect", "str_which")), stringr_xpath)
stringr_calls <- source_expression$xml_find_function_calls(c("str_detect", "str_which"))
stringr_expr <- xml_find_all(stringr_calls, stringr_xpath)

stringr_lints <- xml_nodes_to_lints(
stringr_expr,
Expand Down
4 changes: 3 additions & 1 deletion R/sample_int_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,9 @@ sample_int_linter <- function() {
")

Linter(linter_level = "expression", function(source_expression) {
bad_expr <- xml_find_all(source_expression$xml_find_function_calls("sample"), xpath)
xml_calls <- source_expression$xml_find_function_calls("sample")
bad_expr <- xml_find_all(xml_calls, xpath)

first_call <- xp_call_name(bad_expr, depth = 2L)
original <- sprintf("%s(n)", first_call)
original[!is.na(xml_find_first(bad_expr, "expr[2]/OP-COLON"))] <- "1:n"
Expand Down
3 changes: 2 additions & 1 deletion R/seq_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -85,9 +85,10 @@ seq_linter <- function() {

Linter(linter_level = "expression", function(source_expression) {
xml <- source_expression$xml_parsed_content
seq_calls <- source_expression$xml_find_function_calls("seq")

badx <- c(
xml_find_all(source_expression$xml_find_function_calls("seq"), seq_xpath),
xml_find_all(seq_calls, seq_xpath),
xml_find_all(xml, colon_xpath)
)
class(badx) <- "xml_nodeset"
Expand Down
Loading

0 comments on commit d874444

Please sign in to comment.