I want to be able to find the environment from which the ...
(dots) arguments of a call originate.
Scenario
For example, consider a function
foo <- function(x, ...) {
# do something
}
We want a function env_dots()
, which we invoke from within foo()
, that finds the originating environment of the ...
in a call to foo()
, even when the call to foo()
is deeply nested. That is, if we define
foo <- function(x, ...) {
# find the originating environment of '...'
env <- env_dots()
# do something
}
and nest a call to foo
, like so,
baz <- function(...) {
a <- "You found the dots"
bar(1, 2)
}
bar <- function(...)
foo(...)
then calling baz()
should return the environment in which the ...
in the (nested) call to foo(...)
originates: this is the environment where the call bar(1, 2)
is made, since the 2
(but not the 1
) gets passed to the dots of foo
. In particular, we should get
baz()$a
#> [1] "You found the dots"
Naive implementation of env_dots()
Update — env_dots()
, as defined here, will not work in general, because the final ...
may be populated by arguments that are called at multiple levels of the call stack.
Here's one possibility for env_dots()
:
# mc: match.call() of function from which env_dots() is called
env_dots <- function(mc) {
# Return NULL if initial call invokes no dots
if (!rlang::has_name(mc, "...")) return(NULL)
# Otherwise, climb the call stack until the dots origin is found
stack <- rlang::call_stack()[-1]
l <- length(stack)
i <- 1
while (i <= l && has_dots(stack[[i]]$expr)) i <- i + 1
# return NULL if no dots invoked
if (i <= l) stack[[i + 1]]$env else NULL
}
# Does a call have dots?
has_dots <- function(x) {
if (is.null(x))
return(FALSE)
args <- rlang::lang_tail(x)
any(vapply(args, identical, logical(1), y = quote(...)))
}
This seems to work: with
foo <- function(x, ...)
env_dots(match.call(expand.dots = FALSE))
we get
baz()$a
#> [1] "You found the dots"
bar(1, 2) # 2 gets passed down to the dots of foo()
#> <environment: R_GlobalEnv>
bar(1) # foo() captures no dots
#> NULL
Questions
The above implementation of env_dots()
is not very efficient.
Is there are more skillful way to implement
env_dots()
in rlang and/or base R?How can I move thematch.call()
invocation to withinenv_dots()
?match.call(sys.function(-1), call = sys.call(-1), expand.dots = FALSE)
will indeed work.
Remark — One can't infer the origin environment of the dots from rlang::quos(...)
, because some quosures won't be endowed with the calling environment (e.g., when an expression is a literal object).