R/global_roclet.R

Defines functions globals_filename generated_by block_get_tag_values block_to_globals blocks_to_globals roxy_tag_parse.roxy_tag_autoglobal roxy_tag_parse.roxy_tag_global roclet_clean.roclet_global roclet_output.roclet_global roclet_process.roclet_global global_roclet

Documented in global_roclet

#' Roclet: global
#'
#' @description
#' This roclet automates [utils::globalVariables()] declaration from @global
#' and @autoglobal roxygen tags.
#'
#' Package authors will not typically need to invoke [global_roclet()] directly.
#' Global roclet instances are created by `roxygen2` during [roxygen2::roxygenise()]
#' (or [devtools::document()]).
#'
#' @importFrom roxygen2 roclet
#' @return A [roxygen2::roclet()] instance for declaring [utils::globalVariables()]
#' during [roxygen2::roxygenise()]
#' @export
#'
#' @examples
#' #' @autoglobal
#' foo <- function(x) {
#'   # bar isn't declared -> add to utils::globalVariables()
#'   subset(x, bar == 4)
#' }
#'
#' #' @global bar
#' foo <- function(x) {
#'   # bar is explicitly defined as a global -> add to utils::globalVariables()
#'   subset(x, bar == 4)
#' }
global_roclet <- function() {
  roxygen2::roclet("global")
}

#' @importFrom roxygen2 roclet_process
#' @export
roclet_process.roclet_global <- function(x, blocks, env, base_path) {
  lines <- blocks_to_globals(blocks, options_get_unique(base_path))
  c(generated_by(), "", global_variables(lines))
}

#' @importFrom roxygen2 roclet_output
#' @export
roclet_output.roclet_global <- function(x, results, base_path, ...) {
  brio::write_lines(results, globals_filename(base_path))
  invisible(NULL)
}

#' @importFrom roxygen2 roclet_clean
#' @export
roclet_clean.roclet_global <- function(x, base_path) {
  unlink(globals_filename(base_path), force = TRUE)
}

#' @importFrom roxygen2 roxy_tag_parse
#' @export
roxy_tag_parse.roxy_tag_global <- function(x) {
  if (x$raw == "") return(roxygen2::roxy_tag_warning(x, "requires a value"))

  roxygen2::tag_words(x, min = 1)
}

#' @importFrom roxygen2 roxy_tag_parse
#' @export
roxy_tag_parse.roxy_tag_autoglobal <- function(x) roxygen2::tag_toggle(x)


blocks_to_globals <- function(blocks, unique) {
  globals <- do.call(rbind, lapply(blocks, block_to_globals))
  if (length(globals) == 0) return(NULL)

  fmt_fn <- function(x) paste0("# <", x, ">")

  if (!unique) {
    return(
      paste0(quote_str(globals$global_name), ", ", fmt_fn(globals$fn_name))
    )
  }

  group_fmt <- function(x) {
    paste0(c(
      fmt_fn(x$fn_name),
      paste0(quote_str(x$global_name[1]), ",")
    ))
  }

  groups <- split(globals, globals$global_name)
  unlist(lapply(groups, group_fmt))
}

block_to_globals <- function(block) {
  object <- block$object$value
  name <- block$object$alias %??%
    first(block_get_tag_values(block, c("name", "rdname")))

  # @global
  explicit_globals <- block_get_tag_values(block, "global")

  # @autoglobal
  auto_globals <- if (roxygen2::block_has_tags(block, "autoglobal") && is.function(object)) {
    extract_globals(object)
  }

  globals <- unique(c(explicit_globals, auto_globals))
  if (!is.null(name) && length(globals) != 0)
    data.frame(fn_name = rep_len(name, length(globals)), global_name = globals)
}

block_get_tag_values <- function(block, tags) {
  block_tags <- roxygen2::block_get_tags(block, tags)
  unlist(lapply(block_tags, function(tag) tag$val))
}

generated_by <- function() {
  paste0("# Generated by ", utils::packageName(), ": do not edit by hand")
}

globals_filename <- function(base_path) {
  file.path(base_path, "R", options_get_filename(base_path))
}

Try the roxyglobals package in your browser

Any scripts or data that you put into this service are public.

roxyglobals documentation built on Aug. 21, 2023, 5:14 p.m.