Skip to content

Commit

Permalink
Use newer standalone register for tidyverse methods. `usethis::use_st…
Browse files Browse the repository at this point in the history
…andalone("r-lib/rlang", "s3-register")`
  • Loading branch information
olivroy committed Feb 15, 2024
1 parent 783c4e1 commit 515dbec
Show file tree
Hide file tree
Showing 5 changed files with 250 additions and 87 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,7 @@ SystemRequirements: GDAL (>= 2.0.1), GEOS (>= 3.4.0),
Collate:
'RcppExports.R'
'init.R'
'import-standalone-s3-register.R'
'crs.R'
'bbox.R'
'read.R'
Expand Down
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -393,7 +393,6 @@ export(gdal_utils)
export(gdal_write)
export(gdal_write_mdim)
export(get_key_pos)
export(pivot_wider.sf)
export(plot_sf)
export(rawToHex)
export(read_sf)
Expand Down
187 changes: 187 additions & 0 deletions R/import-standalone-s3-register.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,187 @@
# Standalone file: do not edit by hand
# Source: <https://github.com/r-lib/rlang/blob/main/R/standalone-s3-register.R>
# ----------------------------------------------------------------------
#
# ---
# repo: r-lib/rlang
# file: standalone-s3-register.R
# last-updated: 2022-08-29
# license: https://unlicense.org
# ---
#
# nocov start

#' Register a method for a suggested dependency
#'
#' Generally, the recommended way to register an S3 method is to use the
#' `S3Method()` namespace directive (often generated automatically by the
#' `@export` roxygen2 tag). However, this technique requires that the generic
#' be in an imported package, and sometimes you want to suggest a package,
#' and only provide a method when that package is loaded. `s3_register()`
#' can be called from your package's `.onLoad()` to dynamically register
#' a method only if the generic's package is loaded.
#'
#' For R 3.5.0 and later, `s3_register()` is also useful when demonstrating
#' class creation in a vignette, since method lookup no longer always involves
#' the lexical scope. For R 3.6.0 and later, you can achieve a similar effect
#' by using "delayed method registration", i.e. placing the following in your
#' `NAMESPACE` file:
#'
#' ```
#' if (getRversion() >= "3.6.0") {
#' S3method(package::generic, class)
#' }
#' ```
#'
#' @section Usage in other packages:
#' To avoid taking a dependency on vctrs, you copy the source of
#' [`s3_register()`](https://github.com/r-lib/rlang/blob/main/R/standalone-s3-register.R)
#' into your own package. It is licensed under the permissive
#' [unlicense](https://choosealicense.com/licenses/unlicense/) to make it
#' crystal clear that we're happy for you to do this. There's no need to include
#' the license or even credit us when using this function.
#'
#' @param generic Name of the generic in the form `"pkg::generic"`.
#' @param class Name of the class
#' @param method Optionally, the implementation of the method. By default,
#' this will be found by looking for a function called `generic.class`
#' in the package environment.
#' @examples
#' # A typical use case is to dynamically register tibble/pillar methods
#' # for your class. That way you avoid creating a hard dependency on packages
#' # that are not essential, while still providing finer control over
#' # printing when they are used.
#'
#' .onLoad <- function(...) {
#' s3_register("pillar::pillar_shaft", "vctrs_vctr")
#' s3_register("tibble::type_sum", "vctrs_vctr")
#' }
#' @keywords internal
#' @noRd
s3_register <- function(generic, class, method = NULL) {
stopifnot(is.character(generic), length(generic) == 1)
stopifnot(is.character(class), length(class) == 1)

pieces <- strsplit(generic, "::")[[1]]
stopifnot(length(pieces) == 2)
package <- pieces[[1]]
generic <- pieces[[2]]

caller <- parent.frame()

get_method_env <- function() {
top <- topenv(caller)
if (isNamespace(top)) {
asNamespace(environmentName(top))
} else {
caller
}
}
get_method <- function(method) {
if (is.null(method)) {
get(paste0(generic, ".", class), envir = get_method_env())
} else {
method
}
}

register <- function(...) {
envir <- asNamespace(package)

# Refresh the method each time, it might have been updated by
# `devtools::load_all()`
method_fn <- get_method(method)
stopifnot(is.function(method_fn))


# Only register if generic can be accessed
if (exists(generic, envir)) {
registerS3method(generic, class, method_fn, envir = envir)
} else if (identical(Sys.getenv("NOT_CRAN"), "true")) {
warn <- .rlang_s3_register_compat("warn")

warn(c(
sprintf(
"Can't find generic `%s` in package %s to register S3 method.",
generic,
package
),
"i" = "This message is only shown to developers using devtools.",
"i" = sprintf("Do you need to update %s to the latest version?", package)
))
}
}

# Always register hook in case package is later unloaded & reloaded
setHook(packageEvent(package, "onLoad"), function(...) {
register()
})

# For compatibility with R < 4.1.0 where base isn't locked
is_sealed <- function(pkg) {
identical(pkg, "base") || environmentIsLocked(asNamespace(pkg))
}

# Avoid registration failures during loading (pkgload or regular).
# Check that environment is locked because the registering package
# might be a dependency of the package that exports the generic. In
# that case, the exports (and the generic) might not be populated
# yet (#1225).
if (isNamespaceLoaded(package) && is_sealed(package)) {
register()
}

invisible()
}

.rlang_s3_register_compat <- function(fn, try_rlang = TRUE) {
# Compats that behave the same independently of rlang's presence
out <- switch(
fn,
is_installed = return(function(pkg) requireNamespace(pkg, quietly = TRUE))
)

# Only use rlang if it is fully loaded (#1482)
if (try_rlang &&
requireNamespace("rlang", quietly = TRUE) &&
environmentIsLocked(asNamespace("rlang"))) {
switch(
fn,
is_interactive = return(rlang::is_interactive)
)

# Make sure rlang knows about "x" and "i" bullets
if (utils::packageVersion("rlang") >= "0.4.2") {
switch(
fn,
abort = return(rlang::abort),
warn = return((rlang::warn)),
inform = return(rlang::inform)
)
}
}

# Fall back to base compats

is_interactive_compat <- function() {
opt <- getOption("rlang_interactive")
if (!is.null(opt)) {
opt
} else {
interactive()
}
}

format_msg <- function(x) paste(x, collapse = "\n")
switch(
fn,
is_interactive = return(is_interactive_compat),
abort = return(function(msg) stop(format_msg(msg), call. = FALSE)),
warn = return(function(msg) warning(format_msg(msg), call. = FALSE)),
inform = return(function(msg) message(format_msg(msg)))
)

stop(sprintf("Internal error in rlang shims: Unknown function `%s()`.", fn))
}

# nocov end
8 changes: 4 additions & 4 deletions R/tidyverse-vctrs.R
Original file line number Diff line number Diff line change
Expand Up @@ -91,9 +91,9 @@ vec_cast.sfc.default = function(x, to, ...) {

#nocov start
register_vctrs_methods = function() {
register_s3_method("vctrs", "vec_proxy", "sfc")
register_s3_method("vctrs", "vec_restore", "sfc")
register_s3_method("vctrs", "vec_ptype2", "sfc")
register_s3_method("vctrs", "vec_cast", "sfc")
s3_register("vctrs::vec_proxy", "sfc")
s3_register("vctrs::vec_restore", "sfc")
s3_register("vctrs::vec_ptype2", "sfc")
s3_register("vctrs::vec_cast", "sfc")
}
#nocov end
140 changes: 58 additions & 82 deletions R/tidyverse.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,10 @@ dplyr_reconstruct.sf = function(data, template) {
)
}

#' Tidyverse methods for sf objects (remove .sf suffix!)
#' Tidyverse methods for sf objects
#'
#' Tidyverse methods for sf objects. Geometries are sticky, use \link{as.data.frame} to let \code{dplyr}'s own methods drop them. Use these methods without the .sf suffix and after loading the tidyverse package with the generic (or after loading package tidyverse).
#' Tidyverse methods for sf objects. Geometries are sticky, use \link{as.data.frame} to let \code{dplyr}'s own methods drop them.
#' Use these methods after loading the tidyverse package with the generic (or after loading package tidyverse).
#' @param .data data object of class \link{sf}
#' @param .dots see corresponding function in package \code{dplyr}
#' @param ... other arguments
Expand Down Expand Up @@ -692,86 +693,61 @@ register_all_s3_methods = function() {
requireNamespace("dplyr", quietly = TRUE) &&
utils::packageVersion("dplyr") >= "0.8.99.9000"

if (has_dplyr_1.0)
register_s3_method("dplyr", "dplyr_reconstruct", "sf")
register_s3_method("dplyr", "anti_join", "sf")
register_s3_method("dplyr", "arrange", "sf")
register_s3_method("dplyr", "distinct", "sf")
register_s3_method("dplyr", "filter", "sf")
register_s3_method("dplyr", "full_join", "sf")
register_s3_method("dplyr", "group_by", "sf")
# register_s3_method("dplyr", "group_map", "sf")
register_s3_method("dplyr", "group_split", "sf")
register_s3_method("dplyr", "inner_join", "sf")
register_s3_method("dplyr", "left_join", "sf")
register_s3_method("dplyr", "mutate", "sf")
register_s3_method("dplyr", "rename", "sf")
register_s3_method("dplyr", "rename_with", "sf")
register_s3_method("dplyr", "right_join", "sf")
register_s3_method("dplyr", "rowwise", "sf")
register_s3_method("dplyr", "sample_frac", "sf")
register_s3_method("dplyr", "sample_n", "sf")
register_s3_method("dplyr", "select", "sf")
register_s3_method("dplyr", "semi_join", "sf")
register_s3_method("dplyr", "slice", "sf")
register_s3_method("dplyr", "summarise", "sf")
register_s3_method("dplyr", "transmute", "sf")
register_s3_method("dplyr", "ungroup", "sf")
register_s3_method("tidyr", "drop_na", "sf")
register_s3_method("tidyr", "gather", "sf")
register_s3_method("tidyr", "pivot_longer", "sf")
register_s3_method("tidyr", "pivot_wider", "sf")
register_s3_method("tidyr", "spread", "sf")
register_s3_method("tidyr", "nest", "sf")
register_s3_method("tidyr", "separate", "sf")
register_s3_method("tidyr", "separate_rows", "sf")
register_s3_method("tidyr", "unite", "sf")
register_s3_method("tidyr", "unnest", "sf")
register_s3_method("pillar", "obj_sum", "sfc")
register_s3_method("pillar", "type_sum", "sfc")
register_s3_method("pillar", "pillar_shaft", "sfc")
register_s3_method("spatstat.geom", "as.ppp", "sfc")
register_s3_method("spatstat.geom", "as.ppp", "sf")
register_s3_method("spatstat.geom", "as.owin", "POLYGON")
register_s3_method("spatstat.geom", "as.owin", "MULTIPOLYGON")
register_s3_method("spatstat.geom", "as.owin", "sfc_POLYGON")
register_s3_method("spatstat.geom", "as.owin", "sfc_MULTIPOLYGON")
register_s3_method("spatstat.geom", "as.owin", "sfc")
register_s3_method("spatstat.geom", "as.owin", "sf")
register_s3_method("spatstat.geom", "as.psp", "LINESTRING")
register_s3_method("spatstat.geom", "as.psp", "MULTILINESTRING")
register_s3_method("spatstat.geom", "as.psp", "sfc_MULTILINESTRING")
register_s3_method("spatstat.geom", "as.psp", "sfc")
register_s3_method("spatstat.geom", "as.psp", "sf")
register_s3_method("s2", "as_s2_geography", "sfg")
register_s3_method("s2", "as_s2_geography", "sfc")
register_s3_method("s2", "as_s2_geography", "sf")
if (!has_dplyr_1.0) stop("dplyr (>= 1.0) is required.", call. = FALSE)

s3_register("dplyr::dplyr_reconstruct", "sf")
s3_register("dplyr::anti_join", "sf")
s3_register("dplyr::arrange", "sf")
s3_register("dplyr::distinct", "sf")
s3_register("dplyr::filter", "sf")
s3_register("dplyr::full_join", "sf")
s3_register("dplyr::group_by", "sf")
# s3_register("dplyr::group_map", "sf")
s3_register("dplyr::group_split", "sf")
s3_register("dplyr::inner_join", "sf")
s3_register("dplyr::left_join", "sf")
s3_register("dplyr::mutate", "sf")
s3_register("dplyr::rename", "sf")
s3_register("dplyr::rename_with", "sf")
s3_register("dplyr::right_join", "sf")
s3_register("dplyr::rowwise", "sf")
s3_register("dplyr::sample_frac", "sf")
s3_register("dplyr::sample_n", "sf")
s3_register("dplyr::select", "sf")
s3_register("dplyr::semi_join", "sf")
s3_register("dplyr::slice", "sf")
s3_register("dplyr::summarise", "sf")
s3_register("dplyr::transmute", "sf")
s3_register("dplyr::ungroup", "sf")
s3_register("tidyr::drop_na", "sf")
s3_register("tidyr::gather", "sf")
s3_register("tidyr::pivot_longer", "sf")
s3_register("tidyr::pivot_wider", "sf")
s3_register("tidyr::spread", "sf")
s3_register("tidyr::nest", "sf")
s3_register("tidyr::separate", "sf")
s3_register("tidyr::separate_rows", "sf")
s3_register("tidyr::unite", "sf")
s3_register("tidyr::unnest", "sf")
s3_register("pillar::obj_sum", "sfc")
s3_register("pillar::type_sum", "sfc")
s3_register("pillar::pillar_shaft", "sfc")
s3_register("spatstat.geom::as.ppp", "sfc")
s3_register("spatstat.geom::as.ppp", "sf")
s3_register("spatstat.geom::as.owin", "POLYGON")
s3_register("spatstat.geom::as.owin", "MULTIPOLYGON")
s3_register("spatstat.geom::as.owin", "sfc_POLYGON")
s3_register("spatstat.geom::as.owin", "sfc_MULTIPOLYGON")
s3_register("spatstat.geom::as.owin", "sfc")
s3_register("spatstat.geom::as.owin", "sf")
s3_register("spatstat.geom::as.psp", "LINESTRING")
s3_register("spatstat.geom::as.psp", "MULTILINESTRING")
s3_register("spatstat.geom::as.psp", "sfc_MULTILINESTRING")
s3_register("spatstat.geom::as.psp", "sfc")
s3_register("spatstat.geom::as.psp", "sf")
s3_register("s2::as_s2_geography", "sfg")
s3_register("s2::as_s2_geography", "sfc")
s3_register("s2::as_s2_geography", "sf")
register_vctrs_methods()
}

# from: https://github.com/tidyverse/hms/blob/main/R/zzz.R
# Thu Apr 19 10:53:24 CEST 2018
register_s3_method <- function(pkg, generic, class, fun = NULL) {
stopifnot(is.character(pkg), length(pkg) == 1)
stopifnot(is.character(generic), length(generic) == 1)
stopifnot(is.character(class), length(class) == 1)

if (is.null(fun)) {
fun <- get(paste0(generic, ".", class), envir = parent.frame())
} else {
stopifnot(is.function(fun))
}

if (pkg %in% loadedNamespaces()) {
registerS3method(generic, class, fun, envir = asNamespace(pkg))
}

# Always register hook in case package is later unloaded & reloaded
setHook(
packageEvent(pkg, "onLoad"),
function(...) {
registerS3method(generic, class, fun, envir = asNamespace(pkg))
}
)
}
# nocov end

0 comments on commit 515dbec

Please sign in to comment.