省略号...作为替代函数?

ellipsis ... as function in substitute?

我无法理解 how/why 括号在它们 不应该 ® 的地方起作用。

f = function(...) substitute(...()); f(a, b)
[[1]]
a
[[2]]
b
# but, substitute returns ..1
f2 = function(...) substitute(...); f2(a, b)
a

通常会抛出错误,找不到函数“...”'...' 在不正确的上下文中使用,例如调用 (\(...) ...())(5).

我试过的
我看过 source code of substitute to find out why this doesn't happen here. R Internals 1.1.1 和 1.5.2 说 ... 是 SEXPTYPE DOTSXP,一对承诺列表。这些承诺是 substitute.

提取的内容
#  \-substitute #R
#    \-do_substitute #C
#      \-substituteList #C recursive
#        \-substitute #C

一行一行,卡在了substituteList,其中h...的当前正在处理的元素。这递归地发生在第 2832 行 if (TYPEOF(h) == DOTSXP) h = substituteList(h, R_NilValue);。我没有在源代码中找到 ...() 案例的异常处理,所以我怀疑这之前发生了什么。

?substitute 中,我们发现 替代在纯粹的词汇基础上起作用。这是否意味着 ...() 是一个 parser 技巧?

parse(text = "(\(...) substitute(...()))(a, b)") |> getParseData() |> subset(text == "...", select = c(7, 9))

#>                   token  text
#> 4        SYMBOL_FORMALS   ...
#> 10 SYMBOL_FUNCTION_CALL   ...

第二个省略号在词法分析过程中被识别为函数调用的名称。它不像 |> 那样有自己的令牌。输出是一个配对列表 ( typeof(f(a, b)) ),在本例中是 作为常规列表 (?)。我想这不是解析器技巧。但无论如何,它已经存在了一段时间!

问题:
...() 是如何工作的?

注意: 在引用文档和源代码时,我在 Subversion 存储库中提供了指向 非官方 GitHub mirror of R's official Subversion repository. The links are bound to commit 97b6424 in the GitHub repo, which maps to revision 81461 的链接(本次编辑时的最新版本)。


substitute 是一个“特殊”,其参数未被计算 (doc)。

typeof(substitute)
[1] "special"

这意味着 substitute 的 return 值可能与解析器逻辑不一致,这取决于内部如何处理未评估的参数。

一般来说,substitute 接收调用 ...(<exprs>) 作为形式(伪代码)pairlist(R_DotsSymbol, <exprs>) (doc) 的 LANGSXPsubstitute 调用的上下文决定了 SYMSXP R_DotsSymbol 的处理方式。具体来说,如果 substitute 在一个函数内部被调用,并且 ... 作为形式参数并且 rho 作为它的执行环境,那么

的结果
findVarInFrame3(rho, R_DotsSymbol, TRUE)

在 C 实用程序的主体中 substituteList (source) is either a DOTSXP or R_MissingArg—the latter if and only if f was called without arguments (doc)。在其他情况下,结果是 R_UnboundValue 或(例外地)其他一些 SEXP——后者当且仅当值绑定到 rho 中的名称 ... 时。这些案例中的每一个都由 substituteList.

专门处理

R_DotsSymbol 处理中的多重性是这些 R 语句给出不同结果的原因:

f0 <- function() substitute(...(n = 1)); f0()
## ...(n = 1)
f1 <- function(...) substitute(...(n = 1)); f1()
## $n
## [1] 1
g0 <- function() {... <- quote(x); substitute(...(n = 1))}; g0()
## Error in g0() : '...' used in an incorrect context
g1 <- function(...) {... <- quote(x); substitute(...(n = 1))}; g1()
## Error in g1() : '...' used in an incorrect context
h0 <- function() {... <- NULL; substitute(...(n = 1))}; h0()
## $n
## [1] 1
h1 <- function(...) {... <- NULL; substitute(...(n = 1))}; h1()
## $n
## [1] 1

鉴于 ...(n = 1) 的解析方式,您可能期望 f1 到 return call("...", n = 1)g0g1 到 return call("x", n = 1)h0h1 都会抛出错误,但上述情况并非如此,主要是未记录的原因。

内部

在 R 函数内部调用时 f,

f <- function(...) substitute(...(<exprs>))

substitute 评估对 C 实用程序 do_substitute 的调用——您可以通过查看 here—in which argList gets a LISTSXP of the form pairlist(x, R_MissingArg), where x is a LANGSXP of the form pairlist(R_DotsSymbol, <exprs>) (source).

了解这一点

如果你关注do_substitute的body,那么你会发现从do_substitute传递给substituteListt的值是一个LISTSXP形式为 pairlist(copy_of_x) (source).

因此 substituteList 调用 (source) has exactly one iteration and that the statement CAR(el) == R_DotsSymbol in the body of the loop (source) 中的 while 循环在该迭代中是 false

在条件语句(source)的false分支中,h获取值 pairlist(substituteList(copy_of_x, env))。循环退出并且 substituteList returns hdo_substitute,然后 returns CAR(h) 到 R(来源 1, 2, 3 ).

因此substitute的return值为substituteList(copy_of_x, env),还有待推断这个SEXP的身份。在 this 调用 substituteList 的内部,while 循环有 1+m 次迭代,其中 m 是 [=86= 的次数].在第一次迭代中,循环体中的语句 CAR(el) == R_DotsSymboltrue.

在条件语句 (source), h is either a DOTSXP or R_MissingArg, because f has ... as a formal argument (doc) 的 true 分支中。继续,你会发现 substituteList returns:

  • R_NilValue 如果 h 在第一个 while 迭代中是 R_MissingArg m = 0,

或者,否则,

  • a LISTSXP 列出 h 中的表达式(如果 h 在第一个 while 迭代中是 DOTSXP),然后是 <exprs>(如果 m > 1),所有未评估且没有替换,因为 f 的执行环境在 substitute 调用时是空的。

确实:

f <- function(...) substitute(...())
is.null(f())
## [1] TRUE
f <- function(...) substitute(...(n = 1))
identical(f(a = sin(x), b = zzz), pairlist(a = quote(sin(x)), b = quote(zzz), n = 1))
## [1] TRUE

杂项

FWIW,它帮助我在向 coerce.c 添加一些打印语句后重新编译 R。比如我在do_substitute(source)的正文UNPROTECT(3);之前添加了如下内容:

    Rprintf("CAR(t) == R_DotsSymbol? %d\n",
            CAR(t) == R_DotsSymbol);
    if (TYPEOF(CAR(t)) == LISTSXP || TYPEOF(CAR(t)) == LANGSXP) {
        Rprintf("TYPEOF(CAR(t)) = %s, length(CAR(t)) = %d\n",
                type2char(TYPEOF(CAR(t))), length(CAR(t)));
        Rprintf("CAR(CAR(t)) = R_DotsSymbol? %d\n",
                CAR(CAR(t)) == R_DotsSymbol);
        Rprintf("TYPEOF(CDR(CAR(t))) = %s, length(CDR(CAR(t))) = %d\n",
                type2char(TYPEOF(CDR(CAR(t)))), length(CDR(CAR(t))));
    }
    if (TYPEOF(s) == LISTSXP || TYPEOF(s) == LANGSXP) {
        Rprintf("TYPEOF(s) = %s, length(s) = %d\n",
                type2char(TYPEOF(s)), length(s));
        Rprintf("TYPEOF(CAR(s)) = %s, length(CAR(s)) = %d\n",
                type2char(TYPEOF(CAR(s))), length(CAR(s)));
    }

这帮助我确认了上一行 substituteList 调用的内容:

f <- function(...) substitute(...(n = 1))
invisible(f(hello, world, hello(world)))
CAR(t) == R_DotsSymbol? 0
TYPEOF(CAR(t)) = language, length(CAR(t)) = 2
CAR(CAR(t)) = R_DotsSymbol? 1
TYPEOF(CDR(CAR(t))) = pairlist, length(CDR(CAR(t))) = 1
TYPEOF(s) = pairlist, length(s) = 1
TYPEOF(CAR(s)) = pairlist, length(CAR(s)) = 4
invisible(substitute(...()))
CAR(t) == R_DotsSymbol? 0
TYPEOF(CAR(t)) = language, length(CAR(t)) = 1
CAR(CAR(t)) = R_DotsSymbol? 1
TYPEOF(CDR(CAR(t))) = NULL, length(CDR(CAR(t))) = 0
TYPEOF(s) = pairlist, length(s) = 1
TYPEOF(CAR(s)) = language, length(CAR(s)) = 1

显然,使用调试符号编译 R 和 运行 在调试器下编译 R 也有帮助。

另一个谜题

刚刚注意到这个奇怪的地方:

g <- function(...) substitute(...(n = 1), new.env())
gab <- g(a = sin(x), b = zzz)
typeof(gab)
## [1] "language"
gab
## ...(n = 1)

这里有人可以再深入研究一下,当您提供与 environment() 不同的 env(包括env = NULL).