Skip to content

Commit

Permalink
Merge pull request #1183 from lionel-/ellipsis
Browse files Browse the repository at this point in the history
Move ellipsis to rlang
  • Loading branch information
lionel- committed Apr 28, 2021
2 parents 5246a68 + 527c945 commit df2d0f3
Show file tree
Hide file tree
Showing 25 changed files with 572 additions and 16 deletions.
4 changes: 4 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,10 @@ export(caller_fn)
export(caller_frame)
export(calling)
export(catch_cnd)
export(check_dots_empty)
export(check_dots_empty0)
export(check_dots_unnamed)
export(check_dots_used)
export(check_installed)
export(child_env)
export(chr)
Expand Down
8 changes: 8 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,13 @@
# rlang (development version)

* `check_dots_empty()`, `check_dots_unused()`, and
`check_dots_unnamed()` have been moved from ellipsis to rlang. The
ellipsis package is deprecated and will eventually be archived.

We have added `check_dots_empty0()`. It has a different UI but is
almost as efficient as checking for `missing(...)`. Use this in very
low level functions where a couple microseconds make a difference.

* `s3_register()` no longer fails when generic does not exist. This
prevents failures when users don't have all the last versions of
packages (#1112).
Expand Down
2 changes: 1 addition & 1 deletion R/call.R
Original file line number Diff line number Diff line change
Expand Up @@ -665,7 +665,7 @@ call_match <- function(call = NULL,
defaults = FALSE,
dots_env = NULL,
dots_expand = TRUE) {
check_dots_empty(...)
check_dots_empty0(...)

if (is_null(call)) {
call <- sys.call(sys.parent())
Expand Down
4 changes: 2 additions & 2 deletions R/cnd-entrace.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@
#' }
#' @export
entrace <- function(cnd, ..., top = NULL, bottom = NULL) {
check_dots_empty(...)
check_dots_empty0(...)

if (!missing(cnd) && is_trace(cnd$trace)) {
return()
Expand All @@ -58,7 +58,7 @@ entrace <- function(cnd, ..., top = NULL, bottom = NULL) {
#' @rdname entrace
#' @export
cnd_entrace <- function(cnd, ..., top = NULL, bottom = NULL) {
check_dots_empty(...)
check_dots_empty0(...)

if (!is_null(cnd$trace)) {
return(cnd)
Expand Down
2 changes: 1 addition & 1 deletion R/cnd-signal.R
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@
#'
#' @param cnd A condition object (see [cnd()]). If `NULL`,
#' `cnd_signal()` returns without signalling a condition.
#' @param ... These dots are for extensions and must be empty.
#' @inheritParams dots-empty
#' @seealso [abort()], [warn()] and [inform()] for creating and
#' signalling structured R conditions. See [with_handlers()] for
#' establishing condition handlers.
Expand Down
179 changes: 179 additions & 0 deletions R/dots-ellipsis.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,179 @@
#' Helper for consistent documentation of empty dots
#'
#' Use `` @inheritParams rlang::`dots-empty` `` in your package
#' to consistently document an unused `...` argument.
#'
#' @param ... These dots are for future extensions and must be empty.
#' @name dots-empty
#' @keywords internal
NULL

#' Helper for consistent documentation of used dots
#'
#' Use `` @inheritParams rlang::`dots-used` `` in your package
#' to consistently document an unused `...` argument.
#'
#' @param ... Arguments passed to methods.
#' @name dots-used
#' @keywords internal
NULL

#' Check that all dots have been used
#'
#' Automatically sets exit handler to run when function terminates, checking
#' that all elements of `...` have been evaluated. If you use [on.exit()]
#' elsewhere in your function, make sure to use `add = TRUE` so that you
#' don't override the handler set up by `check_dots_used()`.
#'
#' @param action The action to take when the dots have not been used. One of
#' [rlang::abort()], [rlang::warn()], [rlang::inform()] or [rlang::signal()].
#' @param env Environment in which to look for `...` and to set up handler.
#' @export
#' @examples
#' f <- function(...) {
#' check_dots_used()
#' g(...)
#' }
#'
#' g <- function(x, y, ...) {
#' x + y
#' }
#' f(x = 1, y = 2)
#'
#' try(f(x = 1, y = 2, z = 3))
#' try(f(x = 1, y = 2, 3, 4, 5))
check_dots_used <- function(env = caller_env(), action = abort) {
eval_bare(exit_handler(action), env)
invisible()
}

check_dots <- function(env = caller_env(), action) {
if (.Call(ffi_ellipsis_dots_used, env)) {
return(invisible())
}

proms <- ellipsis_dots(env)
used <- map_lgl(proms, promise_forced)

unused <- names(proms)[!used]
action_dots(
action = action,
message = paste0(length(unused), " arguments in `...` were not used."),
dot_names = unused,
class = "rlib_error_dots_unused",
)
}

exit_handler <- function(action) {
expr(
on.exit((!!check_dots)(environment(), !!action), add = TRUE)
)
}

#' Check that all dots are unnamed
#'
#' In functions like `paste()`, named arguments in `...` are often a
#' sign of misspelled argument names.
#'
#' @inheritParams check_dots_used
#' @param env Environment in which to look for `...`.
#' @export
#' @examples
#' f <- function(..., foofy = 8) {
#' check_dots_unnamed()
#' c(...)
#' }
#'
#' f(1, 2, 3, foofy = 4)
#' try(f(1, 2, 3, foof = 4))
check_dots_unnamed <- function(env = caller_env(), action = abort) {
proms <- ellipsis_dots(env, auto_name = FALSE)
if (length(proms) == 0) {
return()
}

unnamed <- is.na(names(proms))
if (all(unnamed)) {
return(invisible())
}

named <- names(proms)[!unnamed]
action_dots(
action = action,
message = paste0(length(named), " arguments in `...` had unexpected names."),
dot_names = named,
class = "rlib_error_dots_named",
)
}


#' Check that dots are empty
#'
#' Sometimes you just want to use `...` to force your users to fully name
#' the details arguments. This function fails if `...` is not empty.
#'
#' @inheritParams check_dots_used
#' @param env Environment in which to look for `...`.
#' @export
#' @examples
#' f <- function(x, ..., foofy = 8) {
#' check_dots_empty()
#' x + foofy
#' }
#'
#' # This fails because `foofy` can't be matched positionally
#' try(f(1, 4))
#'
#' # This fails because `foofy` can't be matched partially by name
#' try(f(1, foof = 4))
#'
#' # Thanks to `...`, it must be matched exactly
#' f(1, foofy = 4)
check_dots_empty <- function(env = caller_env(), action = abort) {
dots <- ellipsis_dots(env)
if (length(dots) == 0) {
return()
}

action_dots(
action = action,
message = "`...` is not empty.",
dot_names = names(dots),
note = "These dots only exist to allow future extensions and should be empty.",
class = "rlib_error_dots_nonempty"
)
}
#' Check that dots are empty (low level variant)
#'
#' `check_dots_empty0()` is a more efficient version of
#' [check_dots_empty()] with a slightly different interface. Instead
#' of inspecting the current environment for dots, it directly takes
#' `...`. It is only meant for very low level functions where a
#' couple microseconds make a difference.
#'
#' @param ... Dots which should be empty.
#' @keywords internal
#' @export
check_dots_empty0 <- function(...) {
if (nargs()) {
check_dots_empty()
}
}

action_dots <- function(action, message, dot_names, note = NULL, class = NULL, ...) {
message <- format_bullets(c(
message,
i = note,
x = "We detected these problematic arguments:",
set_names(chr_quoted(dot_names), "*"),
i = "Did you misspecify an argument?"
))
action(message, class = c(class, "rlib_error_dots"), ...)
}

promise_forced <- function(x) {
.Call(ffi_ellipsis_promise_forced, x)
}
ellipsis_dots <- function(env = caller_env(), auto_name = TRUE) {
.Call(ffi_ellipsis_dots, env, auto_name)
}
6 changes: 0 additions & 6 deletions R/dots.R
Original file line number Diff line number Diff line change
Expand Up @@ -472,12 +472,6 @@ homonym_enum <- function(nm, dups, nms) {
chr_enumerate(as.character(which(dups)), final = "and")
}

check_dots_empty <- function(...) {
if (nargs()) {
abort("These `...` must be empty")
}
}


# This helper is used when splicing S3 or S4 objects found
# in `!!!`. It is similar to `as.list()`, but the names of
Expand Down
4 changes: 2 additions & 2 deletions R/env-special.R
Original file line number Diff line number Diff line change
Expand Up @@ -307,7 +307,7 @@ is_namespace <- function(x) {
#' is_installed(c("base", "ggplot5"))
#' is_installed(c("base", "ggplot5"), version = c(NA, "5.1.0"))
is_installed <- function(pkg, ..., version = NULL) {
check_dots_empty(...)
check_dots_empty0(...)

if (!all(map_lgl(pkg, function(x) is_true(requireNamespace(x, quietly = TRUE))))) {
return(FALSE)
Expand All @@ -330,7 +330,7 @@ check_installed <- function(pkg,
reason = NULL,
...,
version = NULL) {
check_dots_empty(...)
check_dots_empty0(...)

if (!is_character(pkg)) {
abort("`pkg` must be a package name or a vector of package names.")
Expand Down
2 changes: 1 addition & 1 deletion R/expr.R
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ expr_print <- function(x, ...) {
expr_deparse <- function(x,
...,
width = peek_option("width")) {
check_dots_empty(...)
check_dots_empty0(...)
deparser <- new_quo_deparser(width = width)
quo_deparse(x, deparser)
}
2 changes: 1 addition & 1 deletion R/lifecycle-retired.R
Original file line number Diff line number Diff line change
Expand Up @@ -1418,7 +1418,7 @@ call_standardise <- function(call,
...,
defaults = FALSE,
dots_env = empty_env()) {
check_dots_empty(...)
check_dots_empty()

expr <- get_expr(call)
if (!is_call(expr)) {
Expand Down
2 changes: 1 addition & 1 deletion R/trace.R
Original file line number Diff line number Diff line change
Expand Up @@ -909,7 +909,7 @@ trace_root <- function() {
#' @author Iñaki Ucar (ORCID: 0000-0001-6403-5550)
#' @noRd
trace_pkgs <- function(pkgs, max_level = Inf, ..., regexp = NULL) {
check_dots_empty(...)
check_dots_empty()

# Avoids namespace loading issues
lapply(pkgs, requireNamespace, quietly = TRUE)
Expand Down
9 changes: 9 additions & 0 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,15 @@ reference:
- nse-defuse
- as_label
- as_name
- title: Dots
desc: >
Utils to work with `...`.
contents:
- dots-empty
- dots-used
- check_dots_used
- check_dots_unnamed
- check_dots_empty
- title: Tidy dots
desc: >
Collect arguments contained in `...` with `!!!` and
Expand Down
33 changes: 33 additions & 0 deletions man/check_dots_empty.Rd

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

19 changes: 19 additions & 0 deletions man/check_dots_empty0.Rd

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

27 changes: 27 additions & 0 deletions man/check_dots_unnamed.Rd

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

Loading

0 comments on commit df2d0f3

Please sign in to comment.