Skip to content

Commit

Permalink
Ignore self-import directives
Browse files Browse the repository at this point in the history
  • Loading branch information
lionel- committed Jun 12, 2023
1 parent a34bdf7 commit 3ddd9d7
Show file tree
Hide file tree
Showing 4 changed files with 59 additions and 6 deletions.
4 changes: 4 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
# roxygen2 (development version)

* Import directives are now ignored if they try to import from the
package being documented. This is useful to add self-dependencies in
standalone files meant to be used in other packages (r-lib/usethis#1853).

# roxygen2 7.2.3

* roxygen2 now supports HTML blocks in markdown. They are only included
Expand Down
35 changes: 30 additions & 5 deletions R/namespace.R
Original file line number Diff line number Diff line change
Expand Up @@ -220,7 +220,7 @@ roxy_tag_parse.roxy_tag_import <- function(x) {
}
#' @export
roxy_tag_ns.roxy_tag_import <- function(x, block, env, import_only = FALSE) {
one_per_line("import", x$val)
one_per_line_ignore_current("import", x$val)
}

#' @export
Expand All @@ -229,7 +229,7 @@ roxy_tag_parse.roxy_tag_importClassesFrom <- function(x) {
}
#' @export
roxy_tag_ns.roxy_tag_importClassesFrom <- function(x, block, env, import_only = FALSE) {
repeat_first("importClassesFrom", x$val)
repeat_first_ignore_current("importClassesFrom", x$val)
}

#' @export
Expand All @@ -238,7 +238,7 @@ roxy_tag_parse.roxy_tag_importFrom <- function(x) {
}
#' @export
roxy_tag_ns.roxy_tag_importFrom <- function(x, block, env, import_only = FALSE) {
repeat_first("importFrom", x$val)
repeat_first_ignore_current("importFrom", x$val)
}

#' @export
Expand All @@ -247,7 +247,7 @@ roxy_tag_parse.roxy_tag_importMethodsFrom <- function(x) {
}
#' @export
roxy_tag_ns.roxy_tag_importMethodsFrom <- function(x, block, env, import_only = FALSE) {
repeat_first("importMethodsFrom", x$val)
repeat_first_ignore_current("importMethodsFrom", x$val)
}

#' @export
Expand Down Expand Up @@ -315,12 +315,37 @@ export_s3_method <- function(x) {
}

one_per_line <- function(name, x) {
paste0(name, "(", auto_quote(x), ")")
if (length(x)) {
paste0(name, "(", auto_quote(x), ")")
} else {
NULL
}
}
repeat_first <- function(name, x) {
paste0(name, "(", auto_quote(x[1]), ",", auto_quote(x[-1]), ")")
}

one_per_line_ignore_current <- function(name, x) {
current <- getOption("roxygen2:::package")

# Ignore any occurrence of `current` inside `x`
if (is_string(current)) {
x <- x[x != current]
}

one_per_line(name, x)
}
repeat_first_ignore_current <- function(name, x) {
current <- getOption("roxygen2:::package")

# Ignore the whole command if "first" is `current`
if (is_string(current) && length(x) && x[[1]] == current) {
NULL
} else {
repeat_first(name, x)
}
}

namespace_exports <- function(path) {
if (!file.exists(path)) {
return(character())
Expand Down
9 changes: 8 additions & 1 deletion R/roxygenize-setup.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
roxygen_setup <- function(path = ".", cur_version = NULL) {
roxygen_setup <- function(path = ".",
cur_version = NULL,
frame = caller_env()) {
if (!file.exists(file.path(path, "DESCRIPTION"))) {
cli::cli_abort(
"{.arg package.dir} ({.path {path}}) does not contain a DESCRIPTION"
Expand All @@ -23,6 +25,11 @@ roxygen_setup <- function(path = ".", cur_version = NULL) {
man_path <- file.path(path, "man")
dir.create(man_path, recursive = TRUE, showWarnings = FALSE)

local_options(
"roxygen2:::package" = desc::desc_get("Package", path),
.frame = frame
)

is_first
}

Expand Down
17 changes: 17 additions & 0 deletions tests/testthat/test-namespace.R
Original file line number Diff line number Diff line change
Expand Up @@ -203,6 +203,23 @@ test_that("other namespace tags produce correct output", {
)))
})

test_that("import directives for current package are ignored", {
local_options("roxygen2:::package" = "ignored")

out <- roc_proc_text(namespace_roclet(), "
#' @import ignored
#' @import test ignored test2
#' @importFrom ignored test1 test2
#' @importClassesFrom ignored test1 test2
#' @importMethodsFrom ignored test1 test2
NULL")

expect_equal(sort(out), sort(c(
"import(test)",
"import(test2)"
)))
})

test_that("poorly formed importFrom throws error", {
expect_snapshot_warning(roc_proc_text(namespace_roclet(), "
#' @importFrom test
Expand Down

0 comments on commit 3ddd9d7

Please sign in to comment.