Skip to content

Commit

Permalink
Improve object_usage_linter() (#1715)
Browse files Browse the repository at this point in the history
* improve location information

* small tweaks

* address review comments

Co-authored-by: Michael Chirico <chiricom@google.com>
  • Loading branch information
AshesITR and MichaelChirico authored Oct 16, 2022
1 parent b1780c0 commit 7aee482
Show file tree
Hide file tree
Showing 3 changed files with 45 additions and 20 deletions.
2 changes: 2 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@

* `assignment_linter()` no longer lints assignments in braces that include comments when `allow_trailing = FALSE` (#1701, @ashbaldry)

* `object_usage_linter()` no longer silently ignores usage warnings that don't contain a quoted name (#1714, @AshesITR)

## Changes to defaults

* Set the default for the `except` argument in `duplicate_argument_linter()` to `c("mutate", "transmute")`.
Expand Down
43 changes: 24 additions & 19 deletions R/object_usage_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,9 +122,17 @@ object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) {
},
integer(1L)
)

nodes <- unclass(lintable_symbols)[matched_symbol]
nodes[is.na(matched_symbol)] <- list(fun_assignment)

# fallback to line based matching if no symbol is found
missing_symbol <- is.na(matched_symbol)
nodes[missing_symbol] <- lapply(which(missing_symbol), function(i) {
line_based_match <- xml2::xml_find_first(
fun_assignment,
glue::glue_data(res[i, ], "descendant::expr[@line1 = {line1} and @line2 = {line2}]")
)
if (is.na(line_based_match)) fun_assignment else line_based_match
})

xml_nodes_to_lints(nodes, source_expression = source_expression, lint_message = res$message, type = "warning")
})
Expand Down Expand Up @@ -268,32 +276,29 @@ parse_check_usage <- function(expression,
function_name,
capture(
name = "message",
anything,
one_of(quote, "\u2018"),
capture(name = "name", anything),
one_of(quote, "\u2019"),
anything
zero_or_more(any, type = "lazy"),
maybe(
"'",
capture(name = "name", anything),
"'",
anything
)
),
line_info
)
)

# nocov start
missing <- is.na(res$message)
if (any(missing)) {
res[missing, ] <- re_matches(
vals[missing],
rex(
function_name,
capture(
name = "message",
"possible error in ", capture(name = "name", anything), ": ", anything
),
line_info
)
# TODO (AshesITR): Remove this in the future, if no bugs arise from this safeguard
warning(
"Possible bug in lintr: Couldn't parse usage message ", sQuote(vals[missing][[1L]]), ". ",
"Ignoring ", sum(missing), " usage warnings. Please report an issue at https://github.com/r-lib/lintr/issues."
)
}

res <- res[!is.na(res$message), ]
# nocov end
res <- res[!missing, ]

res$line1 <- as.integer(res$line1) + start_line - 1L
res$line2 <- ifelse(
Expand Down
20 changes: 19 additions & 1 deletion tests/testthat/test-object_usage_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -545,7 +545,8 @@ test_that("fallback works", {
"),
list(
message = rex::rex("no visible global function definition for ", anything, "non_existing_assign<-"),
column_number = 6L
line_number = 2L,
column_number = 3L
),
object_usage_linter()
)
Expand Down Expand Up @@ -606,3 +607,20 @@ test_that("missing libraries don't cause issue", {
object_usage_linter()
)
})

test_that("messages without a quoted name are caught", {
# regression test for #1714
expect_lint(
trim_some("
foo <- function() {
a <- ...
a
}
"),
list(
message = "... may be used in an incorrect context",
line_number = 2L
),
object_usage_linter()
)
})

0 comments on commit 7aee482

Please sign in to comment.