Skip to content

Commit

Permalink
Handle dependencies with no exports (#1509)
Browse files Browse the repository at this point in the history
* Handle dependencies with no exports

Closes #1503

* Simplify; add NEWS

* succinct comment

* Add test

* fix lint

* slightly modify test
  • Loading branch information
IndrajeetPatil authored Aug 25, 2022
1 parent 4b1dd76 commit 7d8c2c4
Show file tree
Hide file tree
Showing 6 changed files with 40 additions and 11 deletions.
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@

## Bug fixes

* `object_length_linter()` does not fail in case there are dependencies with no exports (e.g. data-only packages) (#1509, @IndrajeetPatil).
* `get_source_expressions()` no longer fails on R files that match a knitr pattern (#743, #879, #1406, @AshesITR).
* Parse error lints now appear with the linter name `"error"` instead of `NA` (#1405, @AshesITR).
Also, linting no longer runs if the `source_expressions` contain invalid string data that would cause error messages
Expand Down
26 changes: 16 additions & 10 deletions R/namespace.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,20 +13,25 @@ namespace_imports <- function(path = find_package()) {
}

# this loads the namespaces, but is the easiest way to do it
# test package availablity to avoid failing out as in #1360
# test package availability to avoid failing out as in #1360
# typically, users are running this on their own package directories and thus
# will have the namespace dependencies installed, but we can't guarantee this.
safe_get_exports <- function(ns) {
# check package exists for both import(x) and importFrom(x, y) usages
if (!requireNamespace(ns[[1L]], quietly = TRUE)) {
return(empty_namespace_data())
}

# importFrom directives appear as list(ns, imported_funs)
if (length(ns) > 1L) {
return(data.frame(pkg = ns[[1L]], fun = ns[[2L]], stringsAsFactors = FALSE))
}

data.frame(pkg = ns, fun = getNamespaceExports(ns), stringsAsFactors = FALSE)
# relevant only if there are any exported objects
fun <- getNamespaceExports(ns)
if (length(fun) > 0L) {
data.frame(pkg = ns, fun = fun, stringsAsFactors = FALSE)
}
}

empty_namespace_data <- function() {
Expand All @@ -36,14 +41,15 @@ empty_namespace_data <- function() {
# filter namespace_imports() for S3 generics
# this loads all imported namespaces
imported_s3_generics <- function(ns_imports) {
is_generic <- vapply(
seq_len(nrow(ns_imports)),
function(i) {
fun_obj <- get(ns_imports$fun[i], envir = asNamespace(ns_imports$pkg[i]))
is.function(fun_obj) && is_s3_generic(fun_obj)
},
logical(1L)
)
# `NROW()` for the `NULL` case of 0-export dependencies (cf. #1503)
is_generic <- vapply(
seq_len(NROW(ns_imports)),
function(i) {
fun_obj <- get(ns_imports$fun[i], envir = asNamespace(ns_imports$pkg[i]))
is.function(fun_obj) && is_s3_generic(fun_obj)
},
logical(1L)
)

ns_imports[is_generic, ]
}
Expand Down
3 changes: 3 additions & 0 deletions tests/testthat/dummy_packages/no_export_dep/DESCRIPTION
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
Package: downstream
Version: 0.0.1
Imports: datasets
1 change: 1 addition & 0 deletions tests/testthat/dummy_packages/no_export_dep/NAMESPACE
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import(datasets)
3 changes: 3 additions & 0 deletions tests/testthat/dummy_packages/no_export_dep/R/foo.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
foo <- function() {
a_really_really_long_local_object_name <- 1
}
17 changes: 16 additions & 1 deletion tests/testthat/test-object_length_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,22 @@ test_that("lints S3 generics correctly", {

test_that("object_length_linter won't fail if an imported namespace is unavailable", {
expect_length(
lint_package(test_path("dummy_packages", "missing_dep"), linters = object_length_linter(), parse_settings = FALSE),
lint_package(
test_path("dummy_packages", "missing_dep"),
linters = object_length_linter(),
parse_settings = FALSE
),
3L
)
})

test_that("object_length_linter won't fail if dependency has no exports", {
expect_length(
lint_package(
test_path("dummy_packages", "no_export_dep"),
linters = object_length_linter(),
parse_settings = FALSE
),
1L
)
})

0 comments on commit 7d8c2c4

Please sign in to comment.