Skip to content

Commit

Permalink
Unused import linter (#239)
Browse files Browse the repository at this point in the history
  • Loading branch information
jimhester authored May 16, 2022
1 parent b39f996 commit d52614e
Show file tree
Hide file tree
Showing 11 changed files with 162 additions and 3 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -133,6 +133,7 @@ Collate:
'undesirable_operator_linter.R'
'unneeded_concatenation_linter.R'
'unreachable_code_linter.R'
'unused_import_linter.R'
'vector_logic_linter.R'
'with.R'
'with_id.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ export(undesirable_function_linter)
export(undesirable_operator_linter)
export(unneeded_concatenation_linter)
export(unreachable_code_linter)
export(unused_import_linter)
export(vector_logic_linter)
export(with_defaults)
export(with_id)
Expand Down
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,7 @@ function calls. (#850, #851, @renkun-ken)
This prevents false positive lints in the case of long generic names, e.g.
`very_very_very_long_generic_name.short_class` no longer produces a lint (#871, @AshesITR)
* `object_name_linter()` now correctly detects assignment generics (#843, @jonkeane)
* New `unused_import_linter()` to detect unnecessary `library()` calls in R scripts (#239, @jimhester, @AshesITR)
* `trailing_whitespace_linter()` now also lints completely blank lines by default. This can be disabled by setting the
new argument `allow_empty_lines = TRUE` (#1044, @AshesITR)
* `get_source_expressions()` fixes the `text` value for `STR_CONST` nodes involving 1- or 2-width octal escapes (e.g. `"\1"`) to account for an R parser bug (https://bugs.r-project.org/show_bug.cgi?id=18323)
Expand Down
93 changes: 93 additions & 0 deletions R/unused_import_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,93 @@
#' Check that imported packages are actually used
#'
#' @param allow_ns_usage Suppress lints for packages only used via namespace.
#' This is `FALSE` by default because `pkg::fun()` doesn't require `library(pkg)`.
#' You can use [requireNamespace("pkg")][requireNamespace()] to ensure a package is installed without loading it.
#' @param except_packages Character vector of packages that are ignored.
#' These are usually attached for their side effects.
#'
#' @evalRd rd_tags("unused_import_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
unused_import_linter <- function(allow_ns_usage = FALSE, except_packages = c("bit64", "data.table", "tidyverse")) {
Linter(function(source_expression) {
if (is.null(source_expression$full_xml_parsed_content)) return(list())

import_exprs <- xml2::xml_find_all(
source_expression$full_xml_parsed_content,
"//expr[
expr[SYMBOL_FUNCTION_CALL[text() = 'library' or text() = 'require']]
and
(
not(SYMBOL_SUB[
text() = 'character.only' and
following-sibling::expr[1][NUM_CONST[text() = 'TRUE'] or SYMBOL[text() = 'T']]
]) or
expr[2][STR_CONST]
)
]"
)
if (length(import_exprs) == 0L) {
return(list())
}
imported_pkgs <- xml2::xml_text(xml2::xml_find_first(import_exprs, "expr[STR_CONST|SYMBOL]"))
# as.character(parse(...)) returns one entry per expression
imported_pkgs <- as.character(parse(text = imported_pkgs, keep.source = FALSE))

xp_used_symbols <- paste(
"//SYMBOL_FUNCTION_CALL[not(preceding-sibling::NS_GET)]/text()",
"//SYMBOL/text()",
"//SPECIAL/text()",
sep = " | "
)

used_symbols <- xml2::xml_text(xml2::xml_find_all(source_expression$full_xml_parsed_content, xp_used_symbols))

is_used <- vapply(
imported_pkgs,
function(pkg) {
# Skip excepted packages and packages that are not installed
if (pkg %in% except_packages || !requireNamespace(pkg, quietly = TRUE)) {
return(TRUE)
}

package_exports <- getNamespaceExports(pkg)
any(package_exports %in% used_symbols)
},
logical(1L)
)

is_ns_used <- vapply(
imported_pkgs,
function(pkg) {
ns_usage <- xml2::xml_find_first(source_expression$full_xml_parsed_content, paste0("//SYMBOL_PACKAGE[text() = '", pkg, "']"))
!identical(ns_usage, xml2::xml_missing())
},
logical(1L)
)

is_unused <- !is_used
if (allow_ns_usage) {
is_unused[is_ns_used] <- FALSE
}

lapply(
import_exprs[is_unused],
xml_nodes_to_lint,
source_expression = source_expression,
lint_message = function(import_expr) {
pkg <- get_r_string(xml2::xml_text(xml2::xml_find_first(import_expr, "expr[STR_CONST|SYMBOL]")))
if (is_ns_used[match(pkg, imported_pkgs)]) {
paste0(
"package '", pkg, "' is only used by namespace. ",
"Check that it is installed using loadNamespace() instead."
)
} else {
paste0("package '", pkg, "' is attached but never used.")
}
},
type = "warning",
global = TRUE
)
})
}
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -70,5 +70,6 @@ undesirable_function_linter,style efficiency configurable robustness best_practi
undesirable_operator_linter,style efficiency configurable robustness best_practices
unneeded_concatenation_linter,style readability efficiency
unreachable_code_linter,best_practices readability
unused_import_linter,best_practices common_mistakes configurable
vector_logic_linter,default efficiency best_practices
yoda_test_linter,package_development best_practices readability
1 change: 1 addition & 0 deletions man/best_practices_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/common_mistakes_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/configurable_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 4 additions & 3 deletions man/linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

28 changes: 28 additions & 0 deletions man/unused_import_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

30 changes: 30 additions & 0 deletions tests/testthat/test-unused_import_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
test_that("unused_import_linter lints as expected", {
linter <- unused_import_linter()
expect_lint("library(dplyr)\ntibble(a = 1)", NULL, linter)
# SYMBOL_FUNCTION_CALL usage is detected
expect_lint("library(tidyverse)\ntibble(a = 1)", NULL, linter)
# SYMBOL usage is detected
expect_lint("library(dplyr)\ndo.call(tibble, args = list(a = 1))", NULL, linter)
# SPECIAL usage is detected
expect_lint("library(magrittr)\n1:3 %>% mean()", NULL, linter)

# Missing packages are ignored
expect_lint("library(not.a.package)\ntibble(a = 1)", NULL, linter)
# SYMBOL calls with character.only = TRUE are ignored, even if the argument is a package name
expect_lint("library(dplyr, character.only = TRUE)\n1 + 1", NULL, linter)

msg <- rex::rex("package 'dplyr' is attached but never used")
msg_ns <- rex::rex("package 'dplyr' is only used by namespace")

expect_lint("library(dplyr)\n1 + 1", msg, linter)
expect_lint("require(dplyr)\n1 + 1", msg, linter)
expect_lint("library('dplyr')\n1 + 1", msg, linter)
expect_lint("library('dplyr', character.only = TRUE)\n1 + 1", msg, linter)
# ignore namespaced usages by default, but provide custom lint message
expect_lint("library(dplyr)\ndplyr::tibble(a = 1)", msg_ns, linter)
expect_lint("library(dplyr)\ndplyr::tibble(a = 1)", NULL, unused_import_linter(allow_ns_usage = TRUE))

# ignore packages in except_packages
expect_lint("library(data.table)\n1 + 1", NULL, linter)
expect_lint("library(dplyr)\n1 + 1", NULL, unused_import_linter(except_packages = "dplyr"))
})

0 comments on commit d52614e

Please sign in to comment.