1#  File src/library/base/R/zzz.R
2#  Part of the R package, https://www.R-project.org
3#
4#  Copyright (C) 1995-2021 The R Core Team
5#
6#  This program is free software; you can redistribute it and/or modify
7#  it under the terms of the GNU General Public License as published by
8#  the Free Software Foundation; either version 2 of the License, or
9#  (at your option) any later version.
10#
11#  This program is distributed in the hope that it will be useful,
12#  but WITHOUT ANY WARRANTY; without even the implied warranty of
13#  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14#  GNU General Public License for more details.
15#
16#  A copy of the GNU General Public License is available at
17#  https://www.R-project.org/Licenses/
18
19## top-level assignments that need to be copied to baseloader.R
20as.numeric <- as.double
21is.name <- is.symbol
22
23
24## extracted from existing NAMESPACE files in Dec 2003
25.knownS3Generics <- local({
26
27    ## include the S3 group generics here
28    baseGenerics <- c("Math", "Ops", "Summary", "Complex",
29        "as.character", "as.data.frame", "as.environment", "as.matrix", "as.vector",
30        "cbind", "labels", "print", "rbind", "rep", "seq", "seq.int",
31        "plot", "sequence", "solve", "summary", "t")
32
33    utilsGenerics <- c("edit", "str")
34
35    graphicsGenerics <- c("contour", "hist", "identify", "image",
36        ## "plot",
37        "lines", "pairs", "points", "text")
38
39    statsGenerics <- c("add1", "AIC", "anova", "biplot", "coef",
40        "confint", "deviance", "df.residual", "drop1", "extractAIC",
41        "fitted", "formula", "logLik", "model.frame", "model.matrix",
42        "predict", "profile", "qqnorm", "residuals", "se.contrast",
43        "terms", "update", "vcov")
44
45    tmp <- rep.int(c("base", "utils", "graphics", "stats"),
46                   c(length(baseGenerics), length(utilsGenerics),
47                     length(graphicsGenerics), length(statsGenerics)))
48    names(tmp) <-
49        c(baseGenerics, utilsGenerics, graphicsGenerics, statsGenerics)
50    tmp
51})
52
53###--- Arguments (for printing and QC analysis) for the .Primitive functions ----
54
55## 1) .ArgsEnv : The non-generics .Primitives :
56
57.ArgsEnv <- new.env(hash = TRUE, parent = emptyenv())
58
59assign("::", function(pkg, name) NULL, envir = .ArgsEnv)
60assign(":::", function(pkg, name) NULL, envir = .ArgsEnv)
61assign("%*%", function(x, y) NULL, envir = .ArgsEnv)
62assign("...length", function() NULL, envir = .ArgsEnv)
63assign("...names",  function() NULL, envir = .ArgsEnv)
64assign("...elt", function(n) NULL, envir = .ArgsEnv)
65assign(".C", function(.NAME, ..., NAOK = FALSE, DUP = TRUE, PACKAGE,
66                      ENCODING) NULL,
67       envir = .ArgsEnv)
68assign(".Fortran",
69       function(.NAME, ..., NAOK = FALSE, DUP = TRUE, PACKAGE, ENCODING) NULL,
70       envir = .ArgsEnv)
71assign(".Call", function(.NAME, ..., PACKAGE) NULL, envir = .ArgsEnv)
72assign(".Call.graphics", function(.NAME, ..., PACKAGE) NULL, envir = .ArgsEnv)
73assign(".External", function(.NAME, ..., PACKAGE) NULL, envir = .ArgsEnv)
74assign(".External2", function(.NAME, ..., PACKAGE) NULL, envir = .ArgsEnv)
75assign(".External.graphics", function(.NAME, ..., PACKAGE) NULL,
76       envir = .ArgsEnv)
77assign(".Internal", function(call) NULL, envir = .ArgsEnv)
78assign(".Primitive", function(name) NULL, envir = .ArgsEnv)
79assign(".class2", function(x) NULL, envir = .ArgsEnv)
80assign(".isMethodsDispatchOn", function(onOff = NULL) NULL, envir = .ArgsEnv)
81assign(".primTrace", function(obj) NULL, envir = .ArgsEnv)
82assign(".primUntrace", function(obj) NULL, envir = .ArgsEnv)
83assign(".subset", function(x, ...) NULL, envir = .ArgsEnv)
84assign(".subset2", function(x, ...) NULL, envir = .ArgsEnv)
85assign("UseMethod", function(generic, object) NULL, envir = .ArgsEnv)
86assign("attr", function(x, which, exact = FALSE) NULL, envir = .ArgsEnv)
87assign("attr<-", function(x, which, value) NULL, envir = .ArgsEnv)
88assign("attributes", function(x) NULL, envir = .ArgsEnv)
89assign("attributes<-", function(x, value) NULL, envir = .ArgsEnv)
90assign("baseenv", function() NULL, envir = .ArgsEnv)
91assign("browser",
92       function(text="", condition=NULL, expr = TRUE, skipCalls = 0L) NULL,
93       envir = .ArgsEnv)
94assign("call", function(name, ...) NULL, envir = .ArgsEnv)
95assign("class", function(x) NULL, envir = .ArgsEnv)
96assign("class<-", function(x, value) NULL, envir = .ArgsEnv)
97assign(".cache_class", function(class, extends) NULL, envir = .ArgsEnv)
98assign("emptyenv", function() NULL, envir = .ArgsEnv)
99assign("enc2native", function(x) NULL, envir = .ArgsEnv)
100assign("enc2utf8", function(x) NULL, envir = .ArgsEnv)
101assign("environment<-", function(fun, value) NULL, envir = .ArgsEnv)
102assign("expression", function(...) NULL, envir = .ArgsEnv)
103assign("forceAndCall", function(n, FUN, ...) NULL, envir = .ArgsEnv)
104assign("gc.time", function(on = TRUE) NULL, envir = .ArgsEnv)
105assign("globalenv", function() NULL, envir = .ArgsEnv)
106assign("interactive", function() NULL, envir = .ArgsEnv)
107assign("invisible", function(x) NULL, envir = .ArgsEnv)
108assign("is.atomic", function(x) NULL, envir = .ArgsEnv)
109assign("is.call", function(x) NULL, envir = .ArgsEnv)
110assign("is.character", function(x) NULL, envir = .ArgsEnv)
111assign("is.complex", function(x) NULL, envir = .ArgsEnv)
112assign("is.double", function(x) NULL, envir = .ArgsEnv)
113assign("is.environment", function(x) NULL, envir = .ArgsEnv)
114assign("is.expression", function(x) NULL, envir = .ArgsEnv)
115assign("is.function", function(x) NULL, envir = .ArgsEnv)
116assign("is.integer", function(x) NULL, envir = .ArgsEnv)
117assign("is.language", function(x) NULL, envir = .ArgsEnv)
118assign("is.list", function(x) NULL, envir = .ArgsEnv)
119assign("is.logical", function(x) NULL, envir = .ArgsEnv)
120assign("is.name", function(x) NULL, envir = .ArgsEnv)
121assign("is.null", function(x) NULL, envir = .ArgsEnv)
122assign("is.object", function(x) NULL, envir = .ArgsEnv)
123assign("is.pairlist", function(x) NULL, envir = .ArgsEnv)
124assign("is.raw", function(x) NULL, envir = .ArgsEnv)
125assign("is.recursive", function(x) NULL, envir = .ArgsEnv)
126assign("is.single", function(x) NULL, envir = .ArgsEnv)
127assign("is.symbol", function(x) NULL, envir = .ArgsEnv)
128assign("isS4", function(object) NULL, envir = .ArgsEnv)
129assign("list", function(...) NULL, envir = .ArgsEnv)
130assign("lazyLoadDBfetch", function(key, file, compressed, hook) NULL,
131       envir = .ArgsEnv)
132assign("missing", function(x) NULL, envir = .ArgsEnv)
133assign("nargs", function() NULL, envir = .ArgsEnv)
134assign("nzchar", function(x, keepNA=FALSE) NULL, envir = .ArgsEnv)
135assign("oldClass", function(x) NULL, envir = .ArgsEnv)
136assign("oldClass<-", function(x, value) NULL, envir = .ArgsEnv)
137assign("on.exit", function(expr = NULL, add = FALSE, after = TRUE) NULL, envir = .ArgsEnv)
138assign("pos.to.env", function(x) NULL, envir = .ArgsEnv)
139assign("proc.time", function() NULL, envir = .ArgsEnv)
140assign("quote", function(expr) NULL, envir = .ArgsEnv)
141assign("retracemem", function(x, previous = NULL) NULL, envir = .ArgsEnv)
142assign("seq_along", function(along.with) NULL, envir = .ArgsEnv)
143assign("seq_len", function(length.out) NULL, envir = .ArgsEnv)
144assign("standardGeneric", function(f, fdef) NULL, envir = .ArgsEnv)
145assign("storage.mode<-", function(x, value) NULL, envir = .ArgsEnv)
146assign("substitute", function(expr, env) NULL, envir = .ArgsEnv)
147assign("switch", function(EXPR, ...) NULL, envir = .ArgsEnv)
148assign("tracemem", function(x) NULL, envir = .ArgsEnv)
149assign("unclass", function(x) NULL, envir = .ArgsEnv)
150assign("untracemem", function(x) NULL, envir = .ArgsEnv)
151
152
153## 2) .GenericArgsEnv : The generic .Primitives :
154
155.S3PrimitiveGenerics <-
156  c("anyNA", "as.character", "as.complex", "as.double",
157    "as.environment", "as.integer", "as.logical", "as.call",
158    "as.numeric", "as.raw",
159    "c", "dim", "dim<-", "dimnames", "dimnames<-",
160    "is.array", "is.finite",
161    "is.infinite", "is.matrix", "is.na", "is.nan", "is.numeric",
162    "length", "length<-", "levels<-", "names", "names<-", "rep",
163    "seq.int", "xtfrm")
164
165.GenericArgsEnv <- local({
166    env <- new.env(hash = TRUE, parent = emptyenv())
167    ## those with different arglists are overridden below
168    for(f in .S3PrimitiveGenerics) {
169        fx <- function(x) {}
170        body(fx) <- substitute(UseMethod(ff), list(ff=f))
171        environment(fx) <- .BaseNamespaceEnv
172        assign(f, fx, envir = env)
173    }
174    ## now add the group generics
175    ## round, signif, log, trunc are handled below
176    fx <- function(x) {}
177    for(f in c("abs", "sign", "sqrt", "floor", "ceiling",
178               "exp", "expm1", "log1p", "log10", "log2",
179               "cos", "sin", "tan", "acos", "asin", "atan", "cosh", "sinh",
180               "tanh", "acosh", "asinh", "atanh",
181	       "cospi", "sinpi", "tanpi",
182               "gamma", "lgamma", "digamma", "trigamma",
183               "cumsum", "cumprod", "cummax", "cummin")) {
184        body(fx) <- substitute(UseMethod(ff), list(ff=f))
185        environment(fx) <- .BaseNamespaceEnv
186        assign(f, fx, envir = env)
187    }
188
189    ## ! is unary and handled below
190    fx <- function(e1, e2) {}
191    for(f in c("+", "-", "*", "/", "^", "%%", "%/%", "&", "|",
192               "==", "!=", "<", "<=", ">=", ">")) {
193        body(fx) <- substitute(UseMethod(ff), list(ff=f))
194        environment(fx) <- .BaseNamespaceEnv
195        assign(f, fx, envir = env)
196    }
197
198    for(f in c("all", "any", "sum", "prod", "max", "min", "range")) {
199        fx <- function(..., na.rm = FALSE) {}
200        body(fx) <- substitute(UseMethod(ff), list(ff=f))
201        environment(fx) <- .BaseNamespaceEnv
202        assign(f, fx, envir = env)
203    }
204
205    for(f in c("Arg", "Conj", "Im", "Mod", "Re")) {
206        fx <- function(z) {}
207        body(fx) <- substitute(UseMethod(ff), list(ff=f))
208        environment(fx) <- .BaseNamespaceEnv
209        assign(f, fx, envir = env)
210    }
211    fx <- function(x, recursive = FALSE) UseMethod("anyNA")
212    environment(fx) <- .BaseNamespaceEnv
213    assign("anyNA", fx, envir = env)
214    env
215})
216### do these outside to get the base namespace as the environment.
217assign("!", function(x) UseMethod("!"), envir = .GenericArgsEnv)
218assign("as.character", function(x, ...) UseMethod("as.character"),
219       envir = .GenericArgsEnv)
220assign("as.complex", function(x, ...) UseMethod("as.complex"),
221       envir = .GenericArgsEnv)
222assign("as.double", function(x, ...) UseMethod("as.double"),
223       envir = .GenericArgsEnv)
224assign("as.integer", function(x, ...) UseMethod("as.integer"),
225       envir = .GenericArgsEnv)
226assign("as.logical", function(x, ...) UseMethod("as.logical"),
227       envir = .GenericArgsEnv)
228#assign("as.raw", function(x) UseMethod("as.raw"), envir = .GenericArgsEnv)
229## Conceptually, this is the argument list of  *default* method, not the generic :
230## assign("c", function(..., recursive = FALSE, use.names = TRUE) UseMethod("c"),
231assign("c", function(...) UseMethod("c"),
232       envir = .GenericArgsEnv)
233#assign("dimnames", function(x) UseMethod("dimnames"), envir = .GenericArgsEnv)
234assign("dim<-", function(x, value) UseMethod("dim<-"), envir = .GenericArgsEnv)
235assign("dimnames<-", function(x, value) UseMethod("dimnames<-"),
236       envir = .GenericArgsEnv)
237assign("length<-", function(x, value) UseMethod("length<-"),
238       envir = .GenericArgsEnv)
239assign("levels<-", function(x, value) UseMethod("levels<-"),
240       envir = .GenericArgsEnv)
241assign("log", function(x, base=exp(1)) UseMethod("log"),
242       envir = .GenericArgsEnv)
243assign("names<-", function(x, value) UseMethod("names<-"),
244       envir = .GenericArgsEnv)
245assign("rep", function(x, ...) UseMethod("rep"), envir = .GenericArgsEnv)
246assign("round", function(x, digits=0) UseMethod("round"),
247       envir = .GenericArgsEnv)
248assign("seq.int", function(from, to, by, length.out, along.with, ...)
249       UseMethod("seq.int"), envir = .GenericArgsEnv)
250assign("signif", function(x, digits=6) UseMethod("signif"),
251       envir = .GenericArgsEnv)
252assign("trunc", function(x, ...) UseMethod("trunc"), envir = .GenericArgsEnv)
253#assign("xtfrm", function(x) UseMethod("xtfrm"), envir = .GenericArgsEnv)
254
255## make this the same object as as.double
256assign("as.numeric", get("as.double", envir = .GenericArgsEnv),
257       envir = .GenericArgsEnv)
258
259## Keep this in sync with ../../tools/R/utils.R
260##   tools:::.make_S3_methods_table_for_base()
261## for computing the methods table and
262##   tools:::.deparse_S3_methods_table_for_base()
263## for obtaining the representation used.
264## Always sort with LC_COLLATE=C.
265.S3_methods_table <-
266matrix(c("!", "hexmode",
267         "!", "octmode",
268         "$", "DLLInfo",
269         "$", "package_version",
270         "$<-", "data.frame",
271         "&", "hexmode",
272         "&", "octmode",
273         "*", "difftime",
274         "+", "Date",
275         "+", "POSIXt",
276         "-", "Date",
277         "-", "POSIXt",
278         "/", "difftime",
279         "[", "AsIs",
280         "[", "DLLInfoList",
281         "[", "Date",
282         "[", "Dlist",
283         "[", "POSIXct",
284         "[", "POSIXlt",
285         "[", "data.frame",
286         "[", "difftime",
287         "[", "factor",
288         "[", "hexmode",
289         "[", "listof",
290         "[", "noquote",
291         "[", "numeric_version",
292         "[", "octmode",
293         "[", "simple.list",
294         "[", "table",
295         "[", "warnings",
296         "[<-", "Date",
297         "[<-", "POSIXct",
298         "[<-", "POSIXlt",
299         "[<-", "data.frame",
300         "[<-", "difftime",
301         "[<-", "factor",
302         "[<-", "numeric_version",
303         "[[", "Date",
304         "[[", "POSIXct",
305         "[[", "POSIXlt",
306         "[[", "data.frame",
307         "[[", "factor",
308         "[[", "numeric_version",
309         "[[<-", "POSIXlt",
310         "[[<-", "data.frame",
311         "[[<-", "factor",
312         "[[<-", "numeric_version",
313         "|", "hexmode",
314         "|", "octmode",
315         "Math", "Date",
316         "Math", "POSIXt",
317         "Math", "data.frame",
318         "Math", "difftime",
319         "Math", "factor",
320         "Ops", "Date",
321         "Ops", "POSIXt",
322         "Ops", "data.frame",
323         "Ops", "difftime",
324         "Ops", "factor",
325         "Ops", "numeric_version",
326         "Ops", "ordered",
327         "Summary", "Date",
328         "Summary", "POSIXct",
329         "Summary", "POSIXlt",
330         "Summary", "data.frame",
331         "Summary", "difftime",
332         "Summary", "factor",
333         "Summary", "numeric_version",
334         "Summary", "ordered",
335         "all.equal", "POSIXt",
336         "all.equal", "character",
337         "all.equal", "default",
338         "all.equal", "envRefClass",
339         "all.equal", "environment",
340         "all.equal", "factor",
341         "all.equal", "formula",
342         "all.equal", "function",
343         "all.equal", "language",
344         "all.equal", "list",
345         "all.equal", "numeric",
346         "all.equal", "raw",
347         "anyDuplicated", "array",
348         "anyDuplicated", "data.frame",
349         "anyDuplicated", "default",
350         "anyDuplicated", "matrix",
351         "anyNA", "POSIXlt",
352         "anyNA", "data.frame",
353         "anyNA", "numeric_version",
354         "aperm", "default",
355         "aperm", "table",
356         "as.Date", "POSIXct",
357         "as.Date", "POSIXlt",
358         "as.Date", "character",
359         "as.Date", "default",
360         "as.Date", "factor",
361         "as.Date", "numeric",
362         "as.POSIXct", "Date",
363         "as.POSIXct", "POSIXlt",
364         "as.POSIXct", "default",
365         "as.POSIXct", "numeric",
366         "as.POSIXlt", "Date",
367         "as.POSIXlt", "POSIXct",
368         "as.POSIXlt", "character",
369         "as.POSIXlt", "default",
370         "as.POSIXlt", "factor",
371         "as.POSIXlt", "numeric",
372         "as.array", "default",
373         "as.character", "Date",
374         "as.character", "POSIXt",
375         "as.character", "condition",
376         "as.character", "default",
377         "as.character", "error",
378         "as.character", "factor",
379         "as.character", "hexmode",
380         "as.character", "numeric_version",
381         "as.character", "octmode",
382         "as.character", "srcref",
383         "as.data.frame", "AsIs",
384         "as.data.frame", "Date",
385         "as.data.frame", "POSIXct",
386         "as.data.frame", "POSIXlt",
387         "as.data.frame", "array",
388         "as.data.frame", "character",
389         "as.data.frame", "complex",
390         "as.data.frame", "data.frame",
391         "as.data.frame", "default",
392         "as.data.frame", "difftime",
393         "as.data.frame", "factor",
394         "as.data.frame", "integer",
395         "as.data.frame", "list",
396         "as.data.frame", "logical",
397         "as.data.frame", "matrix",
398         "as.data.frame", "model.matrix",
399         "as.data.frame", "noquote",
400         "as.data.frame", "numeric",
401         "as.data.frame", "numeric_version",
402         "as.data.frame", "ordered",
403         "as.data.frame", "raw",
404         "as.data.frame", "table",
405         "as.data.frame", "ts",
406         "as.data.frame", "vector",
407         "as.double", "POSIXlt",
408         "as.double", "difftime",
409         "as.expression", "default",
410         "as.function", "default",
411         "as.list", "Date",
412         "as.list", "POSIXct",
413         "as.list", "POSIXlt",
414         "as.list", "data.frame",
415         "as.list", "default",
416         "as.list", "difftime",
417         "as.list", "environment",
418         "as.list", "factor",
419         "as.list", "function",
420         "as.list", "numeric_version",
421         "as.logical", "factor",
422         "as.matrix", "POSIXlt",
423         "as.matrix", "data.frame",
424         "as.matrix", "default",
425         "as.matrix", "noquote",
426         "as.null", "default",
427         "as.single", "default",
428         "as.table", "default",
429         "as.vector", "factor",
430         "by", "data.frame",
431         "by", "default",
432         "c", "Date",
433         "c", "POSIXct",
434         "c", "POSIXlt",
435         "c", "difftime",
436         "c", "factor",
437         "c", "noquote",
438         "c", "numeric_version",
439         "c", "warnings",
440         "cbind", "data.frame",
441         "chol", "default",
442         "close", "connection",
443         "close", "srcfile",
444         "close", "srcfilealias",
445         "conditionCall", "condition",
446         "conditionMessage", "condition",
447         "cut", "Date",
448         "cut", "POSIXt",
449         "cut", "default",
450         "determinant", "matrix",
451         "diff", "Date",
452         "diff", "POSIXt",
453         "diff", "default",
454         "diff", "difftime",
455         "dim", "data.frame",
456         "dimnames", "data.frame",
457         "dimnames<-", "data.frame",
458         "droplevels", "data.frame",
459         "droplevels", "factor",
460         "duplicated", "POSIXlt",
461         "duplicated", "array",
462         "duplicated", "data.frame",
463         "duplicated", "default",
464         "duplicated", "matrix",
465         "duplicated", "numeric_version",
466         "duplicated", "warnings",
467         "flush", "connection",
468         "format", "AsIs",
469         "format", "Date",
470         "format", "POSIXct",
471         "format", "POSIXlt",
472         "format", "data.frame",
473         "format", "default",
474         "format", "difftime",
475         "format", "factor",
476         "format", "hexmode",
477         "format", "libraryIQR",
478         "format", "numeric_version",
479         "format", "octmode",
480         "format", "packageInfo",
481         "format", "summaryDefault",
482         "getDLLRegisteredRoutines", "DLLInfo",
483         "getDLLRegisteredRoutines", "character",
484         "is.na", "POSIXlt",
485         "is.na", "data.frame",
486         "is.na", "numeric_version",
487         "is.na<-", "default",
488         "is.na<-", "factor",
489         "is.na<-", "numeric_version",
490         "is.numeric", "Date",
491         "is.numeric", "POSIXt",
492         "is.numeric", "difftime",
493         "isSymmetric", "matrix",
494         "julian", "Date",
495         "julian", "POSIXt",
496         "kappa", "default",
497         "kappa", "lm",
498         "kappa", "qr",
499         "labels", "default",
500         "length", "POSIXlt",
501         "length<-", "Date",
502         "length<-", "POSIXct",
503         "length<-", "POSIXlt",
504         "length<-", "difftime",
505         "length<-", "factor",
506         "levels", "default",
507         "levels<-", "factor",
508         "mean", "Date",
509         "mean", "POSIXct",
510         "mean", "POSIXlt",
511         "mean", "default",
512         "mean", "difftime",
513         "merge", "data.frame",
514         "merge", "default",
515         "months", "Date",
516         "months", "POSIXt",
517         "names", "POSIXlt",
518         "names<-", "POSIXlt",
519         "open", "connection",
520         "open", "srcfile",
521         "open", "srcfilealias",
522         "open", "srcfilecopy",
523         "pretty", "default",
524         "print", "AsIs",
525         "print", "DLLInfo",
526         "print", "DLLInfoList",
527         "print", "DLLRegisteredRoutines",
528         "print", "Date",
529         "print", "Dlist",
530         "print", "NativeRoutineList",
531         "print", "POSIXct",
532         "print", "POSIXlt",
533         "print", "by",
534         "print", "condition",
535         "print", "connection",
536         "print", "data.frame",
537         "print", "default",
538         "print", "difftime",
539         "print", "eigen",
540         "print", "factor",
541         "print", "function",
542         "print", "hexmode",
543         "print", "libraryIQR",
544         "print", "listof",
545         "print", "noquote",
546         "print", "numeric_version",
547         "print", "octmode",
548         "print", "packageInfo",
549         "print", "proc_time",
550         "print", "restart",
551         "print", "rle",
552         "print", "simple.list",
553         "print", "srcfile",
554         "print", "srcref",
555         "print", "summary.table",
556         "print", "summary.warnings",
557         "print", "summaryDefault",
558         "print", "table",
559         "print", "warnings",
560         "qr", "default",
561         "quarters", "Date",
562         "quarters", "POSIXt",
563         "range", "default",
564         "rbind", "data.frame",
565         "rep", "Date",
566         "rep", "POSIXct",
567         "rep", "POSIXlt",
568         "rep", "difftime",
569         "rep", "factor",
570         "rep", "numeric_version",
571         "rev", "default",
572         "round", "Date",
573         "round", "POSIXt",
574         "row.names", "data.frame",
575         "row.names", "default",
576         "row.names<-", "data.frame",
577         "row.names<-", "default",
578         "rowsum", "data.frame",
579         "rowsum", "default",
580         "scale", "default",
581         "seek", "connection",
582         "seq", "Date",
583         "seq", "POSIXt",
584         "seq", "default",
585         "sequence", "default",
586         "solve", "default",
587         "solve", "qr",
588         "sort", "POSIXlt",
589         "sort", "default",
590         "split", "Date",
591         "split", "POSIXct",
592         "split", "data.frame",
593         "split", "default",
594         "split<-", "data.frame",
595         "split<-", "default",
596         "subset", "data.frame",
597         "subset", "default",
598         "subset", "matrix",
599         "summary", "Date",
600         "summary", "POSIXct",
601         "summary", "POSIXlt",
602         "summary", "connection",
603         "summary", "data.frame",
604         "summary", "default",
605         "summary", "factor",
606         "summary", "matrix",
607         "summary", "proc_time",
608         "summary", "srcfile",
609         "summary", "srcref",
610         "summary", "table",
611         "summary", "warnings",
612         "t", "data.frame",
613         "t", "default",
614         "toString", "default",
615         "transform", "data.frame",
616         "transform", "default",
617         "trunc", "Date",
618         "trunc", "POSIXt",
619         "truncate", "connection",
620         "unique", "POSIXlt",
621         "unique", "array",
622         "unique", "data.frame",
623         "unique", "default",
624         "unique", "matrix",
625         "unique", "numeric_version",
626         "unique", "warnings",
627         "units", "difftime",
628         "units<-", "difftime",
629         "weekdays", "Date",
630         "weekdays", "POSIXt",
631         "with", "default",
632         "within", "data.frame",
633         "within", "list",
634         "xtfrm", "AsIs",
635         "xtfrm", "Date",
636         "xtfrm", "POSIXct",
637         "xtfrm", "POSIXlt",
638         "xtfrm", "data.frame",
639         "xtfrm", "default",
640         "xtfrm", "difftime",
641         "xtfrm", "factor",
642         "xtfrm", "numeric_version"),
643       ncol = 2L, byrow = TRUE,
644       dimnames = list(NULL, c("generic", "class")))
645