Skip to content

Commit

Permalink
Add support for imports: field in standalone files
Browse files Browse the repository at this point in the history
  • Loading branch information
lionel- committed Mar 7, 2023
1 parent 711fe64 commit 04e878a
Show file tree
Hide file tree
Showing 5 changed files with 184 additions and 6 deletions.
104 changes: 99 additions & 5 deletions R/use-standalone.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,21 @@
#' It always overwrites an existing standalone file of the same name, making
#' it easy to update previously imported code.
#'
#' @section Supported fields:
#'
#' - `dependencies`: A file or a list of files in the same repo that
#' the standalone file depends on. These files are retrieved
#' automatically by `use_standalone()`.
#'
#' - `imports`: A package or list of packages that the standalone file
#' depends on. A minimal version may be specified in parentheses,
#' e.g. `rlang (>= 1.0.0)`. These dependencies are passed to
#' [use_package()] to ensure they are included in the `Imports:`
#' field of the `DESCRIPTION` file.
#'
#' Note that lists are specified with standard YAML syntax, using
#' square brackets.
#'
#' @inheritParams create_from_github
#' @inheritParams use_github_file
#' @param file Name of standalone file. The `standalone-` prefix and file
Expand Down Expand Up @@ -42,10 +57,24 @@ use_standalone <- function(repo_spec, file = NULL, ref = NULL, host = NULL) {
write_over(proj_path(dest_path), lines, overwrite = TRUE)

dependencies <- standalone_dependencies(lines, path)

for (dependency in dependencies$deps) {
use_standalone(repo_spec, dependency)
}

imports <- dependencies$imports

for (i in seq_len(nrow(imports))) {
import <- imports[i, , drop = FALSE]

if (is.na(import$ver)) {
ver <- NULL
} else {
ver <- import$ver
}
use_package(import$pkg, min_version = ver)
}

invisible()
}

Expand Down Expand Up @@ -114,14 +143,79 @@ standalone_dependencies <- function(lines, path, error_call = caller_env()) {
temp <- withr::local_tempfile(lines = header)
yaml <- rmarkdown::yaml_front_matter(temp)

deps <- yaml$dependencies
if (!is.null(deps) && !is.character(deps)) {
as_chr_field <- function(field) {
if (!is.null(field) && !is.character(field)) {
cli::cli_abort(
"Invalid dependencies specification in {.path {path}}.",
call = error_call
)
}

field %||% character()
}

deps <- as_chr_field(yaml$dependencies)
imports <- as_chr_field(yaml$imports)
imports <- as_version_info(imports, error_call = error_call)

if (any(na.omit(imports$cmp) != ">=")) {
cli::cli_abort(
"Invalid dependencies specification in {.path {path}}.",
"Version specification must use {.code >=}.",
call = error_call
)
}
deps <- deps %||% character()

list(deps = deps)
list(deps = deps, imports = imports)
}

as_version_info <- function(fields, error_call = caller_env()) {
if (!length(fields)) {
return(version_info_df())
}

if (any(grepl(",", fields))) {
msg <- c(
"Version field can't contain comma.",
"i" = "Do you need to wrap in a list?"
)
cli::cli_abort(msg, call = error_call)
}

info <- map(fields, as_version_info_row, error_call = error_call)
inject(rbind(!!!info))
}

as_version_info_row <- function(field, error_call = caller_env()) {
version_regex <- "(.*) \\((.*)\\)$"
has_ver <- grepl(version_regex, field)

if (!has_ver) {
return(version_info_df(field, NA, NA))
}

pkg <- sub(version_regex, "\\1", field)
ver <- sub(version_regex, "\\2", field)

ver <- strsplit(ver, " ")[[1]]

if (!is_character(ver, n = 2) || any(is.na(ver)) || !all(nzchar(ver))) {
cli::cli_abort(
c(
"Can't parse version `{field}` in `imports:` field.",
"i" = "Example of expected version format: `rlang (>= 1.0.0)`."
),
call = error_call
)
}

version_info_df(pkg, ver[[1]], ver[[2]])
}

version_info_df <- function(pkg = chr(), cmp = chr(), ver = chr()) {
df <- data.frame(
pkg = as.character(pkg),
cmp = as.character(cmp),
ver = as.character(ver)
)
structure(df, class = c("tbl", "data.frame"))
}
5 changes: 5 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -114,3 +114,8 @@ maybe_string <- function(x, nm = deparse(substitute(x))) {
check_string(x, nm = nm)
}
}

# For stability of `stringsAsFactors` across versions
data.frame <- function(..., stringsAsFactors = FALSE) {
base::data.frame(..., stringsAsFactors = stringsAsFactors)
}
17 changes: 17 additions & 0 deletions man/use_standalone.Rd

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

20 changes: 20 additions & 0 deletions tests/testthat/_snaps/use-standalone.md
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,26 @@
[3] "# ----------------------------------------------------------------------"
[4] "#"

# can extract imports

Code
extract_imports("# imports: rlang (== 1.0.0)")
Condition
Error in `extract_imports()`:
! Version specification must use `>=`.
Code
extract_imports("# imports: rlang (>= 1.0.0), purrr")
Condition
Error in `extract_imports()`:
! Version field can't contain comma.
i Do you need to wrap in a list?
Code
extract_imports("# imports: foo (>=0.0.0)")
Condition
Error in `extract_imports()`:
! Can't parse version `foo (>=0.0.0)` in `imports:` field.
i Example of expected version format: `rlang (>= 1.0.0)`.

# errors on malformed dependencies

Code
Expand Down
44 changes: 43 additions & 1 deletion tests/testthat/test-use-standalone.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,16 @@ test_that("can import standalone file with dependencies", {
skip_if_offline()
create_local_package()

use_standalone("r-lib/rlang", "types-check", ref = "4670cb233ecc8d11")
# NOTE: Check ref after r-lib/rlang@standalone-dep has been merged
use_standalone("r-lib/rlang", "types-check", ref = "73182fe94")
expect_setequal(
as.character(path_rel(dir_ls(proj_path("R"))), proj_path()),
c("R/import-standalone-types-check.R", "R/import-standalone-obj-type.R")
)

desc <- proj_desc()
imports <- proj_desc()$get_field("Imports")
expect_true(grepl("rlang \\(", imports))
})

test_that("can use full github url", {
Expand Down Expand Up @@ -49,6 +54,43 @@ test_that("can extract dependencies", {
expect_equal(extract_deps("# dependencies: [a, b]"), c("a", "b"))
})

test_that("can extract imports", {
extract_imports <- function(imports) {
out <- standalone_dependencies(
c("# ---", imports, "# ---"),
"test.R",
error_call = current_env()
)
out$imports
}

expect_equal(
extract_imports(NULL),
version_info_df()
)

expect_equal(
extract_imports("# imports: rlang"),
version_info_df("rlang", NA, NA)
)

expect_equal(
extract_imports("# imports: rlang (>= 1.0.0)"),
version_info_df("rlang", ">=", "1.0.0")
)

expect_equal(
extract_imports("# imports: [rlang (>= 1.0.0), purrr]"),
version_info_df(c("rlang", "purrr"), c(">=", NA), c("1.0.0", NA))
)

expect_snapshot(error = TRUE, {
extract_imports("# imports: rlang (== 1.0.0)")
extract_imports("# imports: rlang (>= 1.0.0), purrr")
extract_imports("# imports: foo (>=0.0.0)")
})
})

test_that("errors on malformed dependencies", {
expect_snapshot(error = TRUE, {
standalone_dependencies(c(), "test.R")
Expand Down

0 comments on commit 04e878a

Please sign in to comment.