Title: | Formal Methods and Classes |
---|---|
Description: | Formally defined methods and classes for R objects, plus other programming tools, as described in the reference. |
Authors: | R Core Team |
Maintainer: | R Core Team <[email protected]> |
License: | Part of R 4.4.1 |
Version: | 4.4.1 |
Built: | 2024-06-15 17:27:36 UTC |
Source: | base |
Formally defined methods and classes for R objects, plus other programming tools, as described in the references.
This package provides the “S4” or “S version 4” approach to methods and classes in a functional language.
For basic use of the techniques, start with Introduction and
follow the links there to the key functions for programming, notably
setClass
and setMethod
.
Some specific topics:
Creating one, see setClass
;
examining definitions, see getClassDef
and
classRepresentation; inheritance and coercing,
see is
and as
Basic programming, see
setGeneric
; the class of objects, see
genericFunction; other functions to examine or
manipulate them, see GenericFunctions.
Using classes, see setOldClass
; methods,
see Methods_for_S3.
See ReferenceClasses.
See setClassUnion
.
These pages will have additional links to related topics.
For a complete
list of functions and classes, use library(help="methods")
.
R Core Team
Maintainer: R Core Team [email protected]
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Chapter 10 has some additional details.)
A named list providing instructions for turning builtin and special functions into generic functions.
Functions in R that are defined as .Primitive(<name>)
are not
suitable for formal methods, because they lack the basic reflectance
property. You can't find the argument list for these functions by
examining the function object itself.
Future versions of R may fix this by attaching a formal argument list to the corresponding function. While generally the names of arguments are not checked by the internal code implementing the function, the number of arguments frequently is.
In any case, some definition of a formal argument list is needed if users are to define methods for these functions. In particular, if methods are to be merged from multiple packages, the different sets of methods need to agree on the formal arguments.
In the absence of reflectance, this list provides the relevant information via a dummy function associated with each of the known specials for which methods are allowed.
At the same, the list flags those specials for which methods are
meaningless (e.g., for
) or just a very bad idea (e.g.,
.Primitive
).
A generic function created via setMethod
, for
example, for one of these special functions will have the argument
list from .BasicFunsList
. If no entry exists, the argument
list (x, ...)
is assumed.
Coerce an object to a given class.
as(object, Class, strict=TRUE, ext) as(object, Class) <- value
as(object, Class, strict=TRUE, ext) as(object, Class) <- value
object |
any R object. |
Class |
the name of the class to which |
strict |
logical flag. If If |
value |
The value to use to modify |
ext |
an optional object
defining how |
as(object)
returns the version of this object coerced to be the given
Class
. When used in the replacement form on the left of
an assignment, the portion of the object corresponding to
Class
is replaced by value
.
The operation of as()
in either form depends on the
definition of coerce methods. Methods are defined automatically
when the two classes are related by inheritance; that is, when
one of the classes is a subclass of the other.
Coerce methods are also predefined for basic classes (including all the types of vectors, functions and a few others).
Beyond these two sources of methods, further methods are defined
by calls to the setAs
function. See that
documentation also for details of how coerce methods work. Use
showMethods(coerce)
for a list of all currently defined methods, as in the
example below.
Methods are pre-defined for coercing any object to one of the basic
datatypes. For example, as(x, "numeric")
uses the existing
as.numeric
function. These and all other existing methods
can be listed as shown in the example.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
If you think of using try(as(x, cl))
, consider
canCoerce(x, cl)
instead.
## Show all the existing methods for as() showMethods("coerce")
## Show all the existing methods for as() showMethods("coerce")
Formal classes exist corresponding to the basic R object types, allowing these types to be used in method signatures, as slots in class definitions, and to be extended by new classes.
### The following are all basic vector classes. ### They can appear as class names in method signatures, ### in calls to as(), is(), and new(). "character" "complex" "double" "expression" "integer" "list" "logical" "numeric" "single" "raw" ### the class "vector" ### is a virtual class, extended by all the above ### the class "S4" ### is an object type for S4 objects that do not extend ### any of the basic vector classes. It is a virtual class. ### The following are additional basic classes "NULL" # NULL objects "function" # function objects, including primitives "externalptr" # raw external pointers for use in C code "ANY" # virtual classes used by the methods package itself "VIRTUAL" "missing" "namedList" # the alternative to "list" that preserves # the names attribute
### The following are all basic vector classes. ### They can appear as class names in method signatures, ### in calls to as(), is(), and new(). "character" "complex" "double" "expression" "integer" "list" "logical" "numeric" "single" "raw" ### the class "vector" ### is a virtual class, extended by all the above ### the class "S4" ### is an object type for S4 objects that do not extend ### any of the basic vector classes. It is a virtual class. ### The following are additional basic classes "NULL" # NULL objects "function" # function objects, including primitives "externalptr" # raw external pointers for use in C code "ANY" # virtual classes used by the methods package itself "VIRTUAL" "missing" "namedList" # the alternative to "list" that preserves # the names attribute
If a class is not virtual (see section in Classes_Details
),
objects can be created by calls of the form new(Class, ...)
,
where Class
is the quoted class name, and the remaining
arguments if any are objects to be interpreted as vectors of this
class. Multiple arguments will be concatenated.
The class "expression"
is slightly odd, in that the ...
arguments will not be evaluated; therefore, don't enclose them
in a call to quote()
.
Note that class "list"
is a pure vector. Although lists with
names go back to the earliest versions of S, they are an extension
of the vector concept in that they have an attribute (which can now
be a slot) and which is either NULL
or a character vector of
the same length as the vector. If you want to guarantee that list
names are preserved, use class "namedList"
, rather than
"list"
. Objects from this class must have a names attribute,
corresponding to slot "names"
,
of type "character"
. Internally, R treats names for
lists specially, which makes it impractical to have the corresponding slot in
class "namedList"
be a union of character names and NULL
.
The basic classes include classes for the basic R types. Note that
objects of these types will not usually be S4 objects
(isS4
will return FALSE
), although objects from
classes that contain the basic class will be S4 objects, still with
the same type. The type as
returned by typeof
will sometimes differ from the class,
either just from a choice of terminology (type "symbol"
and
class "name"
, for example) or because there is not a one-to-one
correspondence between class and type (most of the classes that
inherit from class "language"
have type "language"
, for example).
The vector classes extend "vector"
, directly.
Methods are defined to coerce arbitrary objects to
the vector classes, by calling the corresponding basic function, for
example, as(x, "numeric")
calls as.numeric(x)
.
A call to callGeneric
can only appear inside a method
definition. It then results in a call to the current generic
function. The value of that call is the value of callGeneric
.
While it can be called from any method, it is useful and typically
used in methods for group generic functions.
callGeneric(...)
callGeneric(...)
... |
Optionally, the arguments to the function in its next call. If no arguments are included in the call to |
The name and package of the current generic function is stored in the environment of the method definition object. This name is looked up and the corresponding function called.
The statement that passing no arguments to callGeneric
causes
the generic function to be called with the current arguments is
more precisely as follows. Arguments that were missing in the current
call are still missing (remember that "missing"
is a valid
class in a method signature). For a formal argument, say x
, that
appears in the original call, there is a corresponding argument in the
generated call equivalent to x = x
. In effect, this
means that the generic function sees the same actual arguments, but
arguments are evaluated only once.
Using callGeneric
with no arguments is prone to creating
infinite recursion, unless one of the arguments in the signature has
been modified in the current method so that a different method is selected.
The value returned by the new call.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.4 for some details.)
GroupGenericFunctions
for other information
about group generic functions; Methods_Details for the general behavior
of method dispatch
## the method for group generic function Ops ## for signature( e1="structure", e2="vector") function (e1, e2) { value <- callGeneric([email protected], e2) if (length(value) == length(e1)) { [email protected] <- value e1 } else value } ## For more examples ## Not run: showMethods("Ops", includeDefs = TRUE) ## End(Not run)
## the method for group generic function Ops ## for signature( e1="structure", e2="vector") function (e1, e2) { value <- callGeneric(e1@.Data, e2) if (length(value) == length(e1)) { e1@.Data <- value e1 } else value } ## For more examples ## Not run: showMethods("Ops", includeDefs = TRUE) ## End(Not run)
A call to callNextMethod
can only appear inside a method
definition. It then results in a call to the first inherited method
after the current method, with the arguments to the current method
passed down to the next method. The value of that method call is the
value of callNextMethod
.
callNextMethod(...)
callNextMethod(...)
... |
Optionally, the arguments to the function in its next call (but note that the dispatch is as in the detailed description below; the arguments have no effect on selecting the next method.) If no arguments are included in the call to Calling with no arguments is often the natural way to use
|
The ‘next’ method (i.e., the first inherited method) is defined
to be that method which would have been called if the current
method did not exist. This is more-or-less literally what happens: The
current method (to be precise, the method with signature given by the
defined
slot of the method from which callNextMethod
is
called) is deleted from a copy of the methods for the current generic,
and selectMethod
is called to find the next method (the
result is cached in the method object where the call occurred, so the search typically
happens only once per session per combination of argument classes).
The next method is defined from the signature of the current
method, not from the actual classes of the arguments.
In particular, modifying any of the arguments has no effect on the
selection.
As a result, the selected next method can be called with invalid
arguments if the calling function assigns objects of a different
class before the callNextMethod()
call.
Be careful of any assignments to such arguments.
It is possible for the selection of the next method to be ambiguous, even though the original set of methods was consistent. See the section “Ambiguous Selection”.
The statement that the method is called with the current arguments is
more precisely as follows. Arguments that were missing in the current
call are still missing (remember that "missing"
is a valid
class in a method signature). For a formal argument, say x
, that
appears in the original call, there is a corresponding argument in the
next method call equivalent to x = x
. In effect, this
means that the next method sees the same actual arguments, but
arguments are evaluated only once.
The value returned by the selected method.
There are two fairly common situations in which the choice of a next
method is ambiguous, even when the original set of methods uniquely
defines all method selection unambiguously.
In these situations, callNextMethod()
should be replaced,
either by a call to a specific function or by recalling the generic
with different arguments.
The most likely situation arises with methods for binary operators,
typically through one of the group generic functions.
See the example for class "rnum"
below.
Examples of this sort usually require three methods: two for the case
that the first or the second argument comes from the class, and a
third for the case that both arguments come from the class.
If that last method uses callNextMethod
, the other two methods
are equally valid. The ambiguity is exactly the same that required
defining the two-argument method in the first place.
In fact, the two possibilities are equally valid conceptually as well as formally. As in the example below, the logic of the application usually requires selecting a computation explicitly or else calling the generic function with modified arguments to select an appropriate method.
The other likely source of ambiguity arises from a class that inherits
directly from more than one other class (a “mixin” in standard
terminology).
If the generic has methods corresponding to both superclasses, a
method for the current class is again needed to resolve ambiguity.
Using callNextMethod
will again reimpose the ambiguity.
Again, some explicit choice has to be made in the calling method
instead.
These ambiguities are not the result of bad design, but they do require workarounds. Other ambiguities usually reflect inconsistencies in the tree of inheritances, such as a class appearing in more than one place among the superclasses. Such cases should be rare, but with the independent definition of classes in multiple packages, they can't be ruled out.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
callGeneric
to call the generic function with the
current dispatch rules (typically for a group generic function);
Methods_Details for the general behavior of method dispatch.
## callNextMethod() used for the Math, Math2 group generic functions ## A class to automatically round numeric results to "d" digits rnum <- setClass("rnum", slots = c(d = "integer"), contains = "numeric") ## Math functions operate on the rounded numbers, return a plain ## vector. The next method will always be the default, usually a primitive. setMethod("Math", "rnum", function(x) callNextMethod(round(as.numeric(x), x@d))) setMethod("Math2", "rnum", function(x, digits) callNextMethod(round(as.numeric(x), x@d), digits)) ## Examples of callNextMethod with two arguments in the signature. ## For arithmetic and one rnum with anything, callNextMethod with no arguments ## round the full accuracy result, and return as plain vector setMethod("Arith", c(e1 ="rnum"), function(e1, e2) as.numeric(round(callNextMethod(), e1@d))) setMethod("Arith", c(e2 ="rnum"), function(e1, e2) as.numeric(round(callNextMethod(), e2@d))) ## A method for BOTH arguments from "rnum" would be ambiguous ## for callNextMethod(): the two methods above are equally valid. ## The method chooses the smaller number of digits, ## and then calls the generic function, postponing the method selection ## until it's not ambiguous. setMethod("Arith", c(e1 ="rnum", e2 = "rnum"), function(e1, e2) { if(e1@d <= e2@d) callGeneric(e1, as.numeric(e2)) else callGeneric(as.numeric(e1), e2) }) ## For comparisons, callNextMethod with the rounded arguments setMethod("Compare", c(e1 = "rnum"), function(e1, e2) callNextMethod(round(e1, e1@d), round(e2, e1@d))) setMethod("Compare", c(e2 = "rnum"), function(e1, e2) callNextMethod(round(e1, e2@d), round(e2, e2@d))) ## similarly to the Arith case, the method for two "rnum" objects ## can not unambiguously use callNextMethod(). Instead, we rely on ## The rnum() method inhertited from Math2 to return plain vectors. setMethod("Compare", c(e1 ="rnum", e2 = "rnum"), function(e1, e2) { d <- min(e1@d, e2@d) callGeneric(round(e1, d), round(e2, d)) }) set.seed(867) x1 <- rnum(10*runif(5), d=1L) x2 <- rnum(10*runif(5), d=2L) x1+1 x2*2 x1-x2 ## Simple examples to illustrate callNextMethod with and without arguments B0 <- setClass("B0", slots = c(s0 = "numeric")) ## and a function to illustrate callNextMethod f <- function(x, text = "default") { str(x) # print a summary paste(text, ":", class(x)) } setGeneric("f") setMethod("f", "B0", function(x, text = "B0") { cat("B0 method called with s0 =", x@s0, "\n") callNextMethod() }) b0 <- B0(s0 = 1) ## call f() with 2 arguments: callNextMethod passes both to the default method f(b0, "first test") ## call f() with 1 argument: the default "B0" is not passed by callNextMethod f(b0) ## Now, a class that extends B0, with no methods for f() B1 <- setClass("B1", slots = c(s1 = "character"), contains = "B0") b1 <- B1(s0 = 2, s1 = "Testing B1") ## the two cases work as before, by inheriting the "B0" method f(b1, b1@s1) f(b1) B2 <- setClass("B2", contains = "B1") ## And, a method for "B2" that calls with explicit arguments. ## Note that the method selection in callNextMethod ## uses the class of the *argument* to consistently select the "B0" method setMethod("f", "B2", function(x, text = "B1 method") { y <- B1(s0 = -x@s0, s1 ="Modified x") callNextMethod(y, text) }) b2 <- B2(s1 = "Testing B2", s0 = 10) f(b2, b2@s1) f(b2) ## Be careful: the argument passed must be legal for the method selected ## Although the argument here is numeric, it's still the "B0" method that's called setMethod("f", "B2", function(x, text = "B1 method") { callNextMethod(x@s0, text) }) ## Now the call will cause an error: tryCatch(f(b2), error = function(e) cat(e$message,"\n"))
## callNextMethod() used for the Math, Math2 group generic functions ## A class to automatically round numeric results to "d" digits rnum <- setClass("rnum", slots = c(d = "integer"), contains = "numeric") ## Math functions operate on the rounded numbers, return a plain ## vector. The next method will always be the default, usually a primitive. setMethod("Math", "rnum", function(x) callNextMethod(round(as.numeric(x), x@d))) setMethod("Math2", "rnum", function(x, digits) callNextMethod(round(as.numeric(x), x@d), digits)) ## Examples of callNextMethod with two arguments in the signature. ## For arithmetic and one rnum with anything, callNextMethod with no arguments ## round the full accuracy result, and return as plain vector setMethod("Arith", c(e1 ="rnum"), function(e1, e2) as.numeric(round(callNextMethod(), e1@d))) setMethod("Arith", c(e2 ="rnum"), function(e1, e2) as.numeric(round(callNextMethod(), e2@d))) ## A method for BOTH arguments from "rnum" would be ambiguous ## for callNextMethod(): the two methods above are equally valid. ## The method chooses the smaller number of digits, ## and then calls the generic function, postponing the method selection ## until it's not ambiguous. setMethod("Arith", c(e1 ="rnum", e2 = "rnum"), function(e1, e2) { if(e1@d <= e2@d) callGeneric(e1, as.numeric(e2)) else callGeneric(as.numeric(e1), e2) }) ## For comparisons, callNextMethod with the rounded arguments setMethod("Compare", c(e1 = "rnum"), function(e1, e2) callNextMethod(round(e1, e1@d), round(e2, e1@d))) setMethod("Compare", c(e2 = "rnum"), function(e1, e2) callNextMethod(round(e1, e2@d), round(e2, e2@d))) ## similarly to the Arith case, the method for two "rnum" objects ## can not unambiguously use callNextMethod(). Instead, we rely on ## The rnum() method inhertited from Math2 to return plain vectors. setMethod("Compare", c(e1 ="rnum", e2 = "rnum"), function(e1, e2) { d <- min(e1@d, e2@d) callGeneric(round(e1, d), round(e2, d)) }) set.seed(867) x1 <- rnum(10*runif(5), d=1L) x2 <- rnum(10*runif(5), d=2L) x1+1 x2*2 x1-x2 ## Simple examples to illustrate callNextMethod with and without arguments B0 <- setClass("B0", slots = c(s0 = "numeric")) ## and a function to illustrate callNextMethod f <- function(x, text = "default") { str(x) # print a summary paste(text, ":", class(x)) } setGeneric("f") setMethod("f", "B0", function(x, text = "B0") { cat("B0 method called with s0 =", x@s0, "\n") callNextMethod() }) b0 <- B0(s0 = 1) ## call f() with 2 arguments: callNextMethod passes both to the default method f(b0, "first test") ## call f() with 1 argument: the default "B0" is not passed by callNextMethod f(b0) ## Now, a class that extends B0, with no methods for f() B1 <- setClass("B1", slots = c(s1 = "character"), contains = "B0") b1 <- B1(s0 = 2, s1 = "Testing B1") ## the two cases work as before, by inheriting the "B0" method f(b1, b1@s1) f(b1) B2 <- setClass("B2", contains = "B1") ## And, a method for "B2" that calls with explicit arguments. ## Note that the method selection in callNextMethod ## uses the class of the *argument* to consistently select the "B0" method setMethod("f", "B2", function(x, text = "B1 method") { y <- B1(s0 = -x@s0, s1 ="Modified x") callNextMethod(y, text) }) b2 <- B2(s1 = "Testing B2", s0 = 10) f(b2, b2@s1) f(b2) ## Be careful: the argument passed must be legal for the method selected ## Although the argument here is numeric, it's still the "B0" method that's called setMethod("f", "B2", function(x, text = "B1 method") { callNextMethod(x@s0, text) }) ## Now the call will cause an error: tryCatch(f(b2), error = function(e) cat(e$message,"\n"))
Test if an object can be coerced to a given S4 class.
Maybe useful inside if()
to ensure that calling
as(object, Class)
will find a method.
canCoerce(object, Class)
canCoerce(object, Class)
object |
any R object, typically of a formal S4 class. |
Class |
an S4 class (see |
a scalar logical, TRUE
if there is a coerce
method
(as defined by e.g. setAs
) for the signature
(from = class(object), to = Class)
.
as
, setAs
,
selectMethod
, setClass
,
m <- matrix(pi, 2,3) canCoerce(m, "numeric") # TRUE canCoerce(m, "array") # TRUE
m <- matrix(pi, 2,3) canCoerce(m, "numeric") # TRUE canCoerce(m, "array") # TRUE
Combine two matrix-like R objects by columns (cbind2
)
or rows (rbind2
). These are (S4) generic functions with default
methods.
cbind2(x, y, ...) rbind2(x, y, ...)
cbind2(x, y, ...) rbind2(x, y, ...)
x |
any R object, typically matrix-like. |
y |
any R object, typically similar to |
... |
optional arguments for methods. |
The main use of cbind2
(rbind2
) is to be called
recursively by cbind()
(rbind()
) when both of
these requirements are met:
There is at least one argument that is an S4 object, and
S3 dispatch fails (see the Dispatch section under cbind).
The methods on cbind2
and rbind2
effectively define the
type promotion policy when combining a heterogeneous set of
arguments. The homogeneous case, where all objects derive from some S4
class, can be handled via S4 dispatch on the ...
argument via
an externally defined S4 cbind
(rbind
) generic.
Since (for legacy reasons) S3 dispatch is attempted first, it is
generally a good idea to additionally define an S3 method on
cbind
(rbind
) for the S4 class. The S3 method will be
invoked when the arguments include objects of the S4 class, along with
arguments of classes for which no S3 method exists. Also, in case there
is an argument that selects a different S3 method (like the one for
data.frame
), this S3 method serves to introduce an ambiguity in
dispatch that triggers the recursive fallback to cbind2
(rbind2
). Otherwise, the other S3 method would be called, which
may not be appropriate.
A matrix (or matrix like object) combining the columns (or rows) of
x
and y
. Note that methods must construct
colnames
and rownames
from the
corresponding column and row names of x
and y
(but not
from deparsing argument names such as in cbind(...,
deparse.level = d)
for ).
signature(x = "ANY", y = "ANY")
the default method using R's internal code.
signature(x = "ANY", y = "missing")
the default method for one argument using R's internal code.
cbind
, rbind
;
further, cBind
, rBind
in
the Matrix package.
cbind2(1:3, 4) m <- matrix(3:8, 2,3, dimnames=list(c("a","b"), LETTERS[1:3])) cbind2(1:2, m) # keeps dimnames from m ## rbind() and cbind() now make use of rbind2()/cbind2() methods setClass("Num", contains="numeric") setMethod("cbind2", c("Num", "missing"), function(x,y, ...) { cat("Num-miss--meth\n"); as.matrix(x)}) setMethod("cbind2", c("Num","ANY"), function(x,y, ...) { cat("Num-A.--method\n") ; cbind(getDataPart(x), y, ...) }) setMethod("cbind2", c("ANY","Num"), function(x,y, ...) { cat("A.-Num--method\n") ; cbind(x, getDataPart(y), ...) }) a <- new("Num", 1:3) trace("cbind2") cbind(a) cbind(a, four=4, 7:9)# calling cbind2() twice cbind(m,a, ch=c("D","E"), a*3) cbind(1,a, m) # ok with a warning untrace("cbind2")
cbind2(1:3, 4) m <- matrix(3:8, 2,3, dimnames=list(c("a","b"), LETTERS[1:3])) cbind2(1:2, m) # keeps dimnames from m ## rbind() and cbind() now make use of rbind2()/cbind2() methods setClass("Num", contains="numeric") setMethod("cbind2", c("Num", "missing"), function(x,y, ...) { cat("Num-miss--meth\n"); as.matrix(x)}) setMethod("cbind2", c("Num","ANY"), function(x,y, ...) { cat("Num-A.--method\n") ; cbind(getDataPart(x), y, ...) }) setMethod("cbind2", c("ANY","Num"), function(x,y, ...) { cat("A.-Num--method\n") ; cbind(x, getDataPart(y), ...) }) a <- new("Num", 1:3) trace("cbind2") cbind(a) cbind(a, four=4, 7:9)# calling cbind2() twice cbind(m,a, ch=c("D","E"), a*3) cbind(1,a, m) # ok with a warning untrace("cbind2")
You have navigated to an old link to documentation of S4 classes.
For basic use of classes and methods, see Introduction; to
create new class definitions, see setClass
; for
technical details on S4 classes, see Classes_Details.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Class definitions are objects that contain the formal definition of a
class of R objects, usually referred to as an S4 class, to
distinguish them from the informal S3 classes.
This document gives an overview of S4 classes; for
details of the class representation objects, see help for the class
classRepresentation
.
When a class is defined, an object is stored that contains the
information about that class. The object, known as the
metadata defining the class, is not stored under the name of
the class (to allow programmers to write generating functions of
that name), but under a specially constructed name.
To examine the class definition, call getClass
. The
information in the metadata object includes:
The data contained in an object from an S4 class is defined by the slots in the class definition.
Each slot in an object is a component of the object;
like components (that is, elements) of a
list, these may be extracted and set, using the
function slot()
or more often the operator
"@"
. However, they
differ from list components in important ways.
First, slots can only be referred to by name, not by position,
and there is no partial matching of names as with list elements.
All the objects from a particular class have the same set of slot
names; specifically, the slot names that are contained in the
class definition. Each slot in each object always is an object
of the
class specified for this slot in the definition of the current class.
The word “is” corresponds to the R function of the same
name (is
), meaning that the class of the object in
the slot must be the same as the class specified in the
definition, or some class that extends the one in the
definition (a subclass).
A special slot name, .Data
, stands for the
‘data part’ of the object. An object from a class with a
data part is defined by specifying that the class contains one
of the R object types or one of the special pseudo-classes,
matrix
or array
, usually because the definition of
the class, or of one of its superclasses, has included the type
or pseudo-class in its contains
argument. A second
special slot name, .xData
, is used to enable inheritance
from abnormal types such as "environment"
See the section on inheriting from non-S4 classes
for details on the representation and
for the behavior of S3 methods with objects from these classes.
Some slot names correspond to attributes used in old-style S3
objects and in R objects without an explicit class, for
example, the names
attribute. If you define a class for
which that attribute will be set, such as a subclass of named
vectors, you should include "names"
as a slot. See the
definition of class "namedList"
for an example. Using the
names()
assignment to set such names will generate a
warning if there is no names slot and an error if the object in
question is not a vector type. A slot called "names"
can
be used anywhere, but only if it is assigned as a slot, not via
the default names()
assignment.
The definition of a class includes the superclasses —the
classes that this class extends. A
class Fancy
, say, extends a class Simple
if an
object from the Fancy
class has all the capabilities of
the Simple
class (and probably some more as well). In
particular, and very usefully, any method defined to work for a
Simple
object can be applied to a Fancy
object as
well.
This relationship is expressed equivalently by saying that
Simple
is a superclass of Fancy
, or that
Fancy
is a subclass of Simple
.
The direct superclasses of a class are those superclasses
explicitly defined. Direct superclasses can be defined in
three ways. Most commonly, the superclasses are listed in the
contains=
argument in the call to setClass
that creates the subclass. In this case the subclass will
contain all the slots of the superclass, and the relation
between the class is called simple, as it in fact is.
Superclasses can also be defined
explicitly by a call to setIs
; in this case, the
relation requires methods to be specified to go from subclass to
superclass. Thirdly, a class union is a superclass of all the
members of the union. In this case too the relation is simple,
but notice that the relation is defined when the superclass is
created, not when the subclass is created as with the
contains=
mechanism.
The definition of a superclass will also potentially contain its own direct superclasses. These are considered (and shown) as superclasses at distance 2 from the original class; their direct superclasses are at distance 3, and so on. All these are legitimate superclasses for purposes such as method selection.
When superclasses are defined by including the names of
superclasses in the contains=
argument to
setClass
, an object from the class will have all the
slots defined for its own class and all the slots defined
for all its superclasses as well.
The information about the relation between a class and a
particular superclass is encoded as an object of class
SClassExtension
. A list of such objects for
the superclasses (and sometimes for the subclasses) is included in
the metadata object defining the class. If you need to compute
with these objects (for example, to compare the distances), call
the function extends
with argument fullInfo=TRUE
.
The objects from a class created by a call to
new
are defined by the prototype object for the class and by
additional arguments in the call to new
, which are
passed to a method for that class for the function
initialize
.
Each class representation object contains a prototype object
for the class (although for a virtual class the prototype may be
NULL
). The prototype object must have values for all the
slots of the class.
By default, these are the prototypes of the corresponding slot
classes. However, the definition of the class can specify any
valid object for any of the slots.
There are a number of ‘basic’ classes, corresponding to the
ordinary kinds of data occurring in R. For example,
"numeric"
is a class corresponding to numeric vectors.
The other vector basic classes are "logical"
, "integer"
,
"complex"
, "character"
, "raw"
, "list"
and "expression"
.
The prototypes for
the vector classes are vectors of length 0 of the corresponding
type. Notice that basic classes are unusual in that the
prototype object is from the class itself.
In addition to the vector classes there are also basic classes
corresponding to objects in the
language, such as "function"
and "call"
.
These classes are subclasses of the virtual class "language"
.
Finally, there are object types and corresponding basic classes for
“abnormal” objects, such as "environment"
and
"externalptr"
.
These objects do not follow the
functional behavior of the language; in particular, they are not
copied and so cannot have attributes or slots defined locally.
All these classes can be used as slots or as superclasses for any other class definitions, although they do not themselves come with an explicit class. For the abnormal object types, a special mechanism is used to enable inheritance as described below.
A class definition can extend classes other than
regular S4 classes, usually by specifying them in the
contains=
argument to setClass
. Three groups
of such classes behave distinctly:
S3 classes, which must have been registered by a previous call to
setOldClass
(you can check that this has been done
by calling getClass
, which should return a class that
extends oldClass);
One of the R object types, typically a vector type, which then
defines the type of the S4 objects, but also a type such as
environment
that can not be used directly as a type
for an S4 object. See
below.
One of the pseudo-classes matrix
and array
, implying objects with
arbitrary vector types plus the dim
and dimnames
attributes.
This section describes the approach to combining S4 computations with older S3 computations by using such classes as superclasses. The design goal is to allow the S4 class to inherit S3 methods and default computations in as consistent a form as possible.
As part of a general effort to make the S4 and S3 code in R more
consistent, when objects from an S4 class are used as the first
argument to a non-default S3 method, either for an S3 generic function
(one that calls UseMethod
) or for one of the primitive
functions that dispatches S3 methods, an effort is made to provide a
valid object for that method. In particular, if the S4 class extends
an S3 class or matrix
or array
, and there is an S3
method matching one of these classes, the S4 object will be coerced to
a valid S3 object, to the extent that is possible given that there is
no formal definition of an S3 class.
For example, suppose "myFrame"
is an S4 class that includes the
S3 class "data.frame"
in the contains=
argument to
setClass
. If an object from this S4 class is passed to
a function, say as.matrix
, that has an S3 method for
"data.frame"
, the internal code for UseMethod
will convert the object to a data frame; in particular, to an S3
object whose class attribute will be the vector corresponding to the
S3 class (possibly containing multiple class names). Similarly for an
S4 object inheriting from "matrix"
or "array"
, the S4
object will be converted to a valid S3 matrix or array.
Note that the conversion is not applied when an S4 object is
passed to the default S3 method. Some S3 generics attempt to deal
with general objects, including S4 objects. Also, no transformation
is applied to S4 objects that do not correspond to a selected S3
method; in particular, to objects from a class that does not contain
either an S3 class or one of the basic types. See asS4
for the transformation details.
In addition to explicit S3 generic functions, S3 methods are defined for a variety of operators and functions implemented as primitives. These methods are dispatched by some internal C code that operates partly through the same code as real S3 generic functions and partly via special considerations (for example, both arguments to a binary operator are examined when looking for methods). The same mechanism for adapting S4 objects to S3 methods has been applied to these computations as well, with a few exceptions such as generating an error if an S4 object that does not extend an appropriate S3 class or type is passed to a binary operator.
The remainder of this section discusses the mechanisms for
inheriting from basic object types. See matrix
or array
for inhering from the matrix and array
pseudo-classes, or from time-series. For the
corresponding details for inheritance
from S3 classes, see setOldClass
.
An object from a class that directly and simply contains one
of the basic object types in R, has implicitly a corresponding
.Data
slot of that type, allowing computations to extract
or replace the data part while leaving other slots
unchanged. If the type is one that can accept attributes and is
duplicated normally, the inheritance also determines the type of the
object; if the class definition has a .Data
slot
corresponding to a normal type, the class of the
slot determines the type of the object (that is, the value of
typeof(x)
).
For such classes, .Data
is a pseudo-slot; that
is, extracting or setting it modifies the non-slot data in the
object. The functions getDataPart
and
setDataPart
are a cleaner, but essentially
equivalent way to deal with the data part.
Extending a basic type this way allows objects to
use old-style code for the corresponding type as well as S4
methods. Any basic type can be used for .Data
, but
a few types are treated differently because they do not behave like ordinary objects;
for example, "NULL"
, environments, and external pointers.
Classes extend these types by having a slot, .xData
,
itself inherited from an internally defined S4 class. This
slot actually contains an object of the inherited type, to
protect computations from the reference semantics of the type.
Coercing to the nonstandard object type then requires an
actual computation, rather than the "simple"
inclusion
for other types and classes. The intent is that programmers
will not need to take account of the mechanism, but one
implication is that you should not explicitly use the
type of an S4 object to detect inheritance from an arbitrary
object type. Use
is
and similar functions instead.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Methods_Details
for analogous discussion of methods,
setClass
for details of specifying class definitions,
is
,
as
,
new
,
slot
Given a vector of class names or a list of class definitions, the function returns an adjacency matrix of the superclasses of these classes; that is, a matrix with class names as the row and column names and with element [i, j] being 1 if the class in column j is a direct superclass of the class in row i, and 0 otherwise.
The matrix has the information implied by the contains
slot of
the class definitions, but in a form that is often more convenient for
further analysis; for example, an adjacency matrix is used in packages
and other software to construct graph representations of relationships.
classesToAM(classes, includeSubclasses = FALSE, abbreviate = 2)
classesToAM(classes, includeSubclasses = FALSE, abbreviate = 2)
classes |
Either a character vector of class names or a list, whose elements can be either class names or class definitions. The list is convenient, for example, to include the package slot for the class name. See the examples. |
includeSubclasses |
A logical flag; if |
abbreviate |
Control of the abbreviation of the row and/or column labels of the matrix returned: values 0, 1, 2, or 3 abbreviate neither, rows, columns or both. The default, 2, is useful for printing the matrix, since class names tend to be more than one character long, making for spread-out printing. Values of 0 or 3 would be appropriate for making a graph (3 avoids the tendency of some graph plotting software to produce labels in minuscule font size). |
For each of the classes, the calculation gets all the superclass names from the class definition, and finds the edges in those classes' definitions; that is, all the superclasses at distance 1. The corresponding elements of the adjacency matrix are set to 1.
The adjacency matrices for the individual class definitions are merged. Note two possible kinds of inconsistency, neither of which should cause problems except possibly with identically named classes from different packages. Edges are computed from each superclass definition, so that information overrides a possible inference from extension elements with distance > 1 (and it should). When matrices from successive classes in the argument are merged, the computations do not currently check for inconsistencies—this is the area where possible multiple classes with the same name could cause confusion. A later revision may include consistency checks.
As described, a matrix with entries 0 or 1, non-zero values indicating that the class corresponding to the column is a direct superclass of the class corresponding to the row. The row and column names are the class names (without package slot).
extends
and classRepresentation for the underlying information from the class
definition.
## the super- and subclasses of "standardGeneric" ## and "derivedDefaultMethod" am <- classesToAM(list(class(show), class(getMethod(show))), TRUE) am ## Not run: ## the following function depends on the Bioconductor package Rgraphviz plotInheritance <- function(classes, subclasses = FALSE, ...) { if(!require("Rgraphviz", quietly=TRUE)) stop("Only implemented if Rgraphviz is available") mm <- classesToAM(classes, subclasses) classes <- rownames(mm); rownames(mm) <- colnames(mm) graph <- new("graphAM", mm, "directed", ...) plot(graph) cat("Key:\n", paste(abbreviate(classes), " = ", classes, ", ", sep = ""), sep = "", fill = TRUE) invisible(graph) } ## The plot of the class inheritance of the package "graph" require(graph) plotInheritance(getClasses("package:graph")) ## End(Not run)
## the super- and subclasses of "standardGeneric" ## and "derivedDefaultMethod" am <- classesToAM(list(class(show), class(getMethod(show))), TRUE) am ## Not run: ## the following function depends on the Bioconductor package Rgraphviz plotInheritance <- function(classes, subclasses = FALSE, ...) { if(!require("Rgraphviz", quietly=TRUE)) stop("Only implemented if Rgraphviz is available") mm <- classesToAM(classes, subclasses) classes <- rownames(mm); rownames(mm) <- colnames(mm) graph <- new("graphAM", mm, "directed", ...) plot(graph) cat("Key:\n", paste(abbreviate(classes), " = ", classes, ", ", sep = ""), sep = "", fill = TRUE) invisible(graph) } ## The plot of the class inheritance of the package "graph" require(graph) plotInheritance(getClasses("package:graph")) ## End(Not run)
The function className()
generates a
valid references to a class, including the name of the package
containing the class definition. The object returned, from class "className"
, is the
unambiguous way to refer to a class, for example when calling
setMethod
, just in case multiple definitions of the
class exist.
Function
"multipleClasses"
returns information about multiple
definitions of classes with the
same name from different packages.
className(class, package) multipleClasses(details = FALSE)
className(class, package) multipleClasses(details = FALSE)
class , package
|
The character string name of a class and, optionally, of the package
to which it belongs. If argument If there is no package argument or slot, a definition for the class must exist and will be used to define the package. If there are multiple definitions, one will be chosen and a warning printed giving the other possibilities. |
details |
If If |
The table of class definitions used internally can maintain multiple
definitions for classes with the same name but coming from different
packages.
If identical class definitions are encountered, only one class
definition is kept; this occurs most often with S3 classes that have
been specified in calls to setOldClass
. For true
classes, multiple class definitions are unavoidable in general if two
packages happen to have used the same name, independently.
Overriding a class definition in another package with the same name deliberately is usually a bad idea. Although R attempts to keep and use the two definitions (as of version 2.14.0), ambiguities are always possible. It is more sensible to define a new class that extends an existing class but has a different name.
A call to className()
returns an object from class
"className"
.
A call to multipleClasses()
returns either a character
vector or a named list of class definitions. In either case, testing
the length of the returned value for being greater than 0
is a
check for the existence of multiply defined classes.
The class "className"
extends "character"
and has a slot
"package"
, also of class "character"
.
## Not run: className("vector") # will be found, from package "methods" className("vector", "magic") # OK, even though the class doesn't exist className("An unknown class") # Will cause an error ## End(Not run)
## Not run: className("vector") # will be found, from package "methods" className("vector", "magic") # OK, even though the class doesn't exist className("An unknown class") # Will cause an error ## End(Not run)
These are the objects that hold the definition of
classes of objects. They are constructed and stored as meta-data by
calls to the function setClass
. Don't manipulate them
directly, except perhaps to look at individual slots.
Class definitions are stored as metadata in various packages.
Additional metadata supplies information on inheritance (the result of
calls to setIs
). Inheritance information implied by the
class definition itself (because the class contains one or more other
classes) is also constructed automatically.
When a class is to be used in an R session, this information is
assembled to complete the class definition. The completion is a
second object of class "classRepresentation"
, cached for the
session or until something happens to change the information. A call
to getClass
returns the completed definition of a class;
a call to getClassDef
returns the stored definition
(uncompleted).
In particular, completion fills in the upward- and downward-pointing
inheritance information for the class, in slots contains
and
subclasses
respectively. It's in principle important to note
that this information can depend on which packages are installed,
since these may define additional subclasses or superclasses.
slots
:A named list of the slots in this class; the elements of the list are the classes to which the slots must belong (or extend), and the names of the list gives the corresponding slot names.
contains
:A named list of the classes this class
‘contains’; the elements of the list are objects of
SClassExtension
. The list may be only the
direct extensions or all the currently known extensions (see the
details).
virtual
:Logical flag, set to TRUE
if this is
a virtual class.
prototype
:The object that represents the standard
prototype for this class; i.e., the data and slots returned by a
call to new
for this class with no special
arguments. Don't mess with the prototype object directly.
validity
:Optionally, a function to be used to test
the validity of objects from this class.
See validObject
.
access
:Access control information. Not currently used.
className
:The character string name of the class.
package
:The character string name of the package to which the class belongs. Nearly always the package on which the metadata for the class is stored, but in operations such as constructing inheritance information, the internal package name rules.
subclasses
:A named list of the classes known to
extend this class'; the elements of the list are objects of class
SClassExtension
. The list is currently only
filled in when completing the class definition (see the details).
versionKey
:Object of class "externalptr"
;
eventually will perhaps hold some versioning information, but not
currently used.
sealed
:Object of class "logical"
; is this
class sealed? If so, no modifications are allowed.
See function setClass
to supply the information in the
class definition.
See Classes_Details for a more basic discussion of class information.
Special documentation can be supplied to describe the classes and methods that are created by the software in the methods package. Techniques to access this documentation and to create it in R help files are described here.
You can ask for on-line help for class definitions, for specific
methods for a generic function, and for general discussion of
methods for a generic function. These requests use the ?
operator (see help
for a general description of
the operator). Of course, you are at the mercy of the implementer
as to whether there is any documentation on the corresponding
topics.
Documentation on a class uses the argument class
on the left
of the ?
, and the name of the class on the right; for
example,
class ? genericFunction
to ask for documentation on the class "genericFunction"
.
When you want documentation for the methods defined for a particular function, you can ask either for a general discussion of the methods or for documentation of a particular method (that is, the method that would be selected for a particular set of actual arguments).
Overall methods documentation is requested by
calling the ?
operator with methods
as the left-side
argument and the name of the function as the right-side argument. For
example,
methods ? initialize
asks for documentation on the methods for the initialize
function.
Asking for documentation on a particular method is done by giving a
function call expression as the right-hand argument to the "?"
operator. There are two forms, depending on whether you prefer to
give the class names for the arguments or expressions that you intend
to use in the actual call.
If you planned to evaluate a function call, say myFun(x, sqrt(wt))
and wanted to find out something about the method that would be used
for this call, put the call on the right of the "?"
operator:
?myFun(x, sqrt(wt))
A method will be selected, as it would be for the call itself, and
documentation for that method will be requested. If myFun
is
not a generic function, ordinary documentation for the function will
be requested.
If you know the actual classes for which you would like method
documentation, you can supply these explicitly in place of the
argument expressions. In the example above, if you want method
documentation for the first argument having class "maybeNumber"
and the second "logical"
, call the "?"
operator, this
time with a left-side argument method
, and with a function call
on the right using the class names as arguments:
method ? myFun("maybeNumber", "logical")
Once again, a method will be selected, this time corresponding to the specified classes, and method documentation will be requested. This version only works with generic functions.
The two forms each have advantages. The version with actual arguments
doesn't require you to figure out (or guess at) the classes of the
arguments.
On the other hand, evaluating the arguments may take some time,
depending on the example.
The version with class names does require you to pick classes, but
it's otherwise unambiguous. It has a subtler advantage, in that the
classes supplied may be virtual classes, in which case no actual
argument will have specifically this class. The class
"maybeNumber"
, for example, might be a class union (see the
example for setClassUnion
).
In either form, methods will be selected as they would be in actual
computation, including use of inheritance and group generic
functions. See selectMethod
for the details, since it is
the function used to find the appropriate method.
The on-line documentation for methods and classes uses some extensions to the R documentation format to implement the requests for class and method documentation described above. See the document Writing R Extensions for the available markup commands (you should have consulted this document already if you are at the stage of documenting your software).
In addition to the specific markup commands to be described, you can create an initial, overall file with a skeleton of documentation for the methods defined for a particular generic function:
promptMethods("myFun")
will create a file, ‘myFun-methods.Rd’ with a skeleton of
documentation for the methods defined for function myFun
.
The output from promptMethods
is suitable if you want to
describe all or most of the methods for the function in one file,
separate from the documentation of the generic function itself.
Once the file has been filled in and moved to the ‘man’
subdirectory of your source package, requests for methods
documentation will use that file, both for specific methods
documentation as described above, and for overall documentation
requested by
methods ? myFun
You are not required to use promptMethods
, and if you do, you
may not want to use the entire file created:
If you want to document the methods in the file containing the
documentation for the generic function itself, you can
cut-and-paste to move the \alias
lines and the
Methods
section from the file created by
promptMethods
to the existing file.
On the other hand, if these are auxiliary methods, and you only
want to document the added or modified software, you should strip
out all but the relevant \alias
lines for the methods of
interest, and remove all but the corresponding \item
entries in the Methods
section. Note that in this case you
will usually remove the first \alias
line as well, since
that is the marker for general methods documentation on this
function (in the example, ‘\alias{myfun-methods}’).
If you simply want to direct documentation for one or more methods to a particular R documentation file, insert the appropriate alias.
...
in Method SignaturesThe “...” argument in R functions is treated specially, in that it matches zero, one or more actual arguments (and so, objects). A mechanism has been added to R to allow “...” as the signature of a generic function. Methods defined for such functions will be selected and called when all the arguments matching “...” are from the specified class or from some subclass of that class.
Beginning with version 2.8.0 of R, S4 methods can be dispatched (selected and called) corresponding to the special argument “...”. Currently, “...” cannot be mixed with other formal arguments: either the signature of the generic function is “...” only, or it does not contain “...”. (This restriction may be lifted in a future version.)
Given a suitable generic function, methods are specified in the
usual way by a call to setMethod
. The method
definition must be written expecting all the arguments corresponding
to “...” to be from the class specified in the method's signature,
or from a class that extends that class (i.e., a subclass of that
class).
Typically the methods will pass “...” down to another function or will create a list of the arguments and iterate over that. See the examples below.
When you have a computation that is suitable for more than one existing
class, a convenient approach may be to define a union of these
classes by a call to setClassUnion
. See the example
below.
See Methods_Details for a general discussion. The following assumes you have read the “Method Selection and Dispatch” section of that documentation.
A method selecting on “...” is specified by a single class in the
call to setMethod
. If all the actual arguments
corresponding to “...” have this class, the corresponding method is
selected directly.
Otherwise, the class of each argument and that class' superclasses are computed, beginning with the first “...” argument. For the first argument, eligible methods are those for any of the classes. For each succeeding argument that introduces a class not considered previously, the eligible methods are further restricted to those matching the argument's class or superclasses. If no further eligible classes exist, the iteration breaks out and the default method, if any, is selected.
At the end of the iteration, one or more methods may be eligible.
If more than one, the selection looks for the method with the least
distance to the actual arguments. For each argument, any inherited
method corresponds to a distance, available from the contains
slot of the class definition. Since the same class can arise for
more than one argument, there may be several distances associated
with it. Combining them is inevitably arbitrary: the current
computation uses the minimum distance. Thus, for example, if a
method matched one argument directly, one as first generation
superclass and another as a second generation superclass, the
distances are 0, 1 and 2. The current selection computation would
use distance 0 for this
method. In particular, this selection criterion tends to use a method that
matches exactly one or more of the arguments' class.
As with ordinary method selection, there may be multiple methods with the same distance. A warning message is issued and one of the methods is chosen (the first encountered, which in this case is rather arbitrary).
Notice that, while the computation examines all arguments, the essential cost of dispatch goes up with the number of distinct classes among the arguments, likely to be much smaller than the number of arguments when the latter is large.
Methods dispatching on “...” were introduced in version 2.8.0 of
R. The initial implementation of the corresponding selection and
dispatch is in an R function, for flexibility while the new
mechanism is being studied. In this implementation, a local version
of standardGeneric
is inserted in the generic function's
environment. The local version selects a method according to the
criteria above and calls that method, from the environment of the
generic function. This is slightly different from the action taken
by the C implementation when “...” is not involved. Aside from the
extra computing time required, the method is evaluated in a true
function call, as opposed to the special context constructed by the
C version (which cannot be exactly replicated in R code.) However,
situations in which different computational results would
be obtained have not been encountered so far, and seem very
unlikely.
Methods dispatching on arguments other than “...” are cached by storing
the inherited method in the table of all methods, where it will be
found on the next selection with the same combination of classes
in the actual arguments (but not used for inheritance searches).
Methods based on “...” are also cached, but not found quite
as immediately. As noted, the selected method depends only on the
set of classes that occur in the “...” arguments. Each of
these classes can appear one or more times, so many combinations of
actual argument classes will give rise to the same effective
signature. The selection computation first computes and sorts the
distinct classes encountered. This gives a label that will be
cached in the table of all methods, avoiding any further search for
inherited classes after the first occurrence. A call to
showMethods
will expose such inherited methods.
The intention is that the “...” features will be added to the standard C code when enough experience with them has been obtained. It is possible that at the same time, combinations of “...” with other arguments in signatures may be supported.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
For the general discussion of methods, see Methods_Details and links from there.
cc <- function(...)c(...) setGeneric("cc") setMethod("cc", "character", function(...)paste(...)) setClassUnion("Number", c("numeric", "complex")) setMethod("cc", "Number", function(...) sum(...)) setClass("cdate", contains = "character", slots = c(date = "Date")) setClass("vdate", contains = "vector", slots = c(date = "Date")) cd1 <- new("cdate", "abcdef", date = Sys.Date()) cd2 <- new("vdate", "abcdef", date = Sys.Date()) stopifnot(identical(cc(letters, character(), cd1), paste(letters, character(), cd1))) # the "character" method stopifnot(identical(cc(letters, character(), cd2), c(letters, character(), cd2))) # the default, because "vdate" doesn't extend "character" stopifnot(identical(cc(1:10, 1+1i), sum(1:10, 1+1i))) # the "Number" method stopifnot(identical(cc(1:10, 1+1i, TRUE), c(1:10, 1+1i, TRUE))) # the default stopifnot(identical(cc(), c())) # no arguments implies the default method setGeneric("numMax", function(...)standardGeneric("numMax")) setMethod("numMax", "numeric", function(...)max(...)) # won't work for complex data setMethod("numMax", "Number", function(...) paste(...)) # should not be selected w/o complex args stopifnot(identical(numMax(1:10, pi, 1+1i), paste(1:10, pi, 1+1i))) stopifnot(identical(numMax(1:10, pi, 1), max(1:10, pi, 1))) try(numMax(1:10, pi, TRUE)) # should be an error: no default method ## A generic version of paste(), dispatching on the "..." argument: setGeneric("paste", signature = "...") setMethod("paste", "Number", function(..., sep, collapse) c(...)) stopifnot(identical(paste(1:10, pi, 1), c(1:10, pi, 1)))
cc <- function(...)c(...) setGeneric("cc") setMethod("cc", "character", function(...)paste(...)) setClassUnion("Number", c("numeric", "complex")) setMethod("cc", "Number", function(...) sum(...)) setClass("cdate", contains = "character", slots = c(date = "Date")) setClass("vdate", contains = "vector", slots = c(date = "Date")) cd1 <- new("cdate", "abcdef", date = Sys.Date()) cd2 <- new("vdate", "abcdef", date = Sys.Date()) stopifnot(identical(cc(letters, character(), cd1), paste(letters, character(), cd1))) # the "character" method stopifnot(identical(cc(letters, character(), cd2), c(letters, character(), cd2))) # the default, because "vdate" doesn't extend "character" stopifnot(identical(cc(1:10, 1+1i), sum(1:10, 1+1i))) # the "Number" method stopifnot(identical(cc(1:10, 1+1i, TRUE), c(1:10, 1+1i, TRUE))) # the default stopifnot(identical(cc(), c())) # no arguments implies the default method setGeneric("numMax", function(...)standardGeneric("numMax")) setMethod("numMax", "numeric", function(...)max(...)) # won't work for complex data setMethod("numMax", "Number", function(...) paste(...)) # should not be selected w/o complex args stopifnot(identical(numMax(1:10, pi, 1+1i), paste(1:10, pi, 1+1i))) stopifnot(identical(numMax(1:10, pi, 1), max(1:10, pi, 1))) try(numMax(1:10, pi, TRUE)) # should be an error: no default method ## A generic version of paste(), dispatching on the "..." argument: setGeneric("paste", signature = "...") setMethod("paste", "Number", function(..., sep, collapse) c(...)) stopifnot(identical(paste(1:10, pi, 1), c(1:10, pi, 1)))
"environment"
A formal class for R environments.
Objects can be created by calls of the form new("environment", ...)
.
The arguments in ..., if any, should be named and will be assigned to
the newly created environment.
signature(from = "ANY", to = "environment")
:
calls as.environment
.
signature(object = "environment")
:
Implements the assignments in the new environment. Note that the
object
argument is ignored; a new environment is
always created, since environments are not protected by copying.
"envRefClass"
Support Class to Implement R Objects using Reference Semantics
The software described here is an initial version. The eventual goal is to support reference-style classes with software in R itself or using inter-system interfaces. The current implementation (R version 2.12.0) is preliminary and subject to change, and currently includes only the R-only implementation. Developers are encouraged to experiment with the software, but the description here is more than usually subject to change.
This class implements basic reference-style semantics for R
objects. Objects normally do not come directly from this class, but
from subclasses defined by a call to setRefClass
.
The documentation below is technical background describing the implementation, but applications
should use the interface documented under setRefClass
,
in particular the $
operator and field accessor functions as
described there.
The design of reference classes for R divides those classes up
according to the mechanism used for implementing references, fields,
and class methods.
Each version of this mechanism is defined by a basic reference
class, which must implement a set of methods and provide some
further information used by setRefClass
.
The required methods are for operators $
and $<-
to
get and set a field in an object, and for initialize
to
initialize objects.
To support these methods, the basic reference class needs to have some
implementation mechanism to store and retrieve data from fields in the
object.
The mechanism needs to be consistent with reference semantics; that
is, changes made to the contents of an object are global, seen by any
code accessing that object, rather than only local to the function
call where the change takes place.
As described below, class envRefClass
implements reference
semantics through specialized use of environment
objects.
Other basic reference classes may use an interface to a language such
as Java or C++ using reference semantics for classes.
Usually, the R user will be able to invoke class methods on the
class, using the $
operator. The basic reference class
method for $
needs to make this possible. Essentially, the
operator must return an R function corresponding to the object and
the class method name.
Class methods may include an implementation of data abstraction, in
the sense that fields are accessed by “get” and “set”
methods. The basic reference class provides this facility by setting
the "fieldAccessorGenerator"
slot in its definition to a
function of one variable.
This function will be called by setRefClass
with the
vector of field names as arguments.
The generator function must return a list of defined accessor
functions.
An element corresponding to a get operation is invoked with no
arguments and should extract the corresponding field; an element for a
set operation will be invoked with a single argument, the value to be
assigned to the field.
The implementation needs to supply the object, since that is not an
argument in the method invocation.
The mechanism used currently by envRefClass
is described below.
Two virtual classes are supplied to test for reference objects:
is(x, "refClass")
tests whether x
comes from a class
defined using the reference class mechanism described here;
is(x, "refObject")
tests whether the object has reference
semantics generally, including the previous classes and also classes
inheriting from the R types with reference semantics, such as
"environment"
.
Installed class methods are "classMethodDefinition"
objects,
with slots that identify the name of the function as a class method
and the other class methods called from this method.
The latter information is determined heuristically when the class is
defined by using the codetools
recommended package. This
package must be installed when reference classes are defined, but is
not needed in order to use existing reference classes.
John Chambers
Definitions of functions and/or methods from a source file are
inserted into a package, using the trace
mechanism.
Typically, this allows testing or debugging modified versions of a few
functions without reinstalling a large package.
evalSource(source, package = "", lock = TRUE, cache = FALSE) insertSource(source, package = "", functions = , methods = , force = )
evalSource(source, package = "", lock = TRUE, cache = FALSE) insertSource(source, package = "", functions = , methods = , force = )
source |
A file to be parsed and evaluated by The argument to |
package |
Optionally, the name of the package to which the new code corresponds and into which it will be inserted. Although the computations will attempt to infer the package if it is omitted, the safe approach is to supply it. In the case of a package that is not attached to the search list, the package name must be supplied. |
functions , methods
|
Optionally, the character-string names of the functions to be
used in the insertion. Names supplied in the If |
lock , cache
|
Optional arguments to control the actions taken by The default settings are generally recommended, the |
force |
If |
The source
file is parsed and evaluated, suppressing by default
the actual caching of method and class definitions contained in it, so
that functions and methods can be tested out in a reversible way.
The result, if all goes well, is an environment containing the
assigned objects and metadata corresponding to method and class definitions
in the source file.
From this environment, the objects are inserted into the package, into
its namespace if it has one, for use during the current session or
until reverting to the original version by a call to
untrace
.
The insertion is done by calls to the internal version of
trace
, to make reversion possible.
Because the trace mechanism is used, only function-type objects will be inserted, functions themselves or S4 methods.
When the functions
and methods
arguments are both
omitted, insertSource
selects all suitable objects from the
result of evaluating the source
file.
In all cases, only objects in the source file that differ from the corresponding objects in the package are inserted. The definition of “differ” is that either the argument list (including default expressions) or the body of the function is not identical. Note that in the case of a method, there need be no specific method for the corresponding signature in the package: the comparison is made to the method that would be selected for that signature.
Nothing in the computation requires that the source file supplied be
the same file as in the original package source, although that case is
both likely and sensible if one is revising the package. Nothing in
the computations compares source files: the objects generated by
evaluating source
are compared as objects to the content of the package.
An object from class "sourceEnvironment"
, a subclass of
"environment"
(see the section on the class)
The environment contains the versions
of all object resulting from evaluation of the source file.
The class also has slots for the time of creation, the source file
and the package name.
Future extensions may use these objects for versioning or other code tools.
The object returned can be used in debugging (see the section on that
topic) or as the source
argument in a future call to insertSource
. If only some of the
revised functions were inserted in the first call, others can be
inserted in a later call without re-evaluating the source file, by
supplying the environment and optionally suitable functions
and/or methods
argument.
Once a function or method has been inserted into a package by
insertSource
, it can be studied by the standard debugging tools;
for example, debug
or the various versions of
trace
.
Calls to trace
should take the extra argument edit
= env
, where env
is the value returned by the call to
evalSource
.
The trace mechanism has been used to install the revised version from
the source file, and supplying the argument ensures that it is this
version, not the original, that will be traced. See the example
below.
To turn tracing off, but retain the source version, use trace(x,
edit = env)
as in the example. To return to the original version
from the package, use untrace(x)
.
"sourceEnvironment"
Objects from this class can be treated as environments, to extract the
version of functions and methods generated by evalSource
.
The objects also have the following slots:
packageName
:The character-string name of the package to which the source code corresponds.
dateCreated
: The date and time that the source file was
evaluated (usually from a call to Sys.time
).
sourceFile
:The character-string name of the source file used.
Note that using the environment does not change the dateCreated
.
trace
for the underlying mechanism, and also for the
edit=
argument that can be used for somewhat similar purposes;
that function and also debug
and
setBreakpoint
, for techniques more oriented to
traditional debugging styles.
The present function is directly intended for the case that one is
modifying some of the source for an existing package, although it can
be used as well by inserting debugging code in the source (more useful
if the debugging involved is non-trivial). As noted in the details
section, the source
file need not be the same one in the original package source.
## Not run: ## Suppose package P0 has a source file "all.R" ## First, evaluate the source, and from it ## insert the revised version of methods for summary() env <- insertSource("./P0/R/all.R", package = "P0", methods = "summary") ## now test one of the methods, tracing the version from the source trace("summary", signature = "myMat", browser, edit = env) ## After testing, remove the browser() call but keep the source trace("summary", signature = "myMat", edit = env) ## Now insert all the (other) revised functions and methods ## without re-evaluating the source file. ## The package name is included in the object env. insertSource(env) ## End(Not run)
## Not run: ## Suppose package P0 has a source file "all.R" ## First, evaluate the source, and from it ## insert the revised version of methods for summary() env <- insertSource("./P0/R/all.R", package = "P0", methods = "summary") ## now test one of the methods, tracing the version from the source trace("summary", signature = "myMat", browser, edit = env) ## After testing, remove the browser() call but keep the source trace("summary", signature = "myMat", edit = env) ## Now insert all the (other) revised functions and methods ## without re-evaluating the source file. ## The package name is included in the object env. insertSource(env) ## End(Not run)
Functions to find classes: isClass
tests for a class;
findClass
returns the name(s) of packages containing the
class; getClasses
returns the names of all the classes in an
environment, typically a namespace. To examine the definition of a class, use getClass
.
isClass(Class, formal=TRUE, where) getClasses(where, inherits = missing(where)) findClass(Class, where, unique = "") ## The remaining functions are retained for compatibility ## but not generally recommended removeClass(Class, where) resetClass(Class, classDef, where) sealClass(Class, where)
isClass(Class, formal=TRUE, where) getClasses(where, inherits = missing(where)) findClass(Class, where, unique = "") ## The remaining functions are retained for compatibility ## but not generally recommended removeClass(Class, where) resetClass(Class, classDef, where) sealClass(Class, where)
Class |
character string name for the class. The functions will
usually take a class definition instead of the string. To restrict
the class to those defined in a particular package, set the
|
where |
the To restrict the search to classes in a particular package, use |
formal |
|
unique |
if |
inherits |
in a call to |
classDef |
For |
isClass
:Is this the name of a formally defined class?
getClasses
:The names of all the classes formally defined on where
. If
called with no argument, all the classes visible from the
calling function (if called from the top-level, all the classes
in any of the environments on the search list). The
where
argument is used to search only in a particular package.
findClass
:The list of environments in
which a class definition of Class
is found. If
where
is supplied, a list is still returned, either empty
or containing the environment corresponding to where
.
By default when called from the R session, the global
environment and all the currently
attached packages are searched.
If unique
is supplied as a character string,
findClass
will warn if there is more than one definition
visible (using the string to identify the purpose of the call),
and will generate an error if no definition can be found.
The remaining functions are retained for back-compatibility and internal use, but not generally recommended.
removeClass
:Remove the definition of this class. This can't be used if the class is in another package, and would rarely be needed in source code defining classes in a package.
resetClass
:Reset the internal definition of a class. Not legitimate for a class definition not in this package and rarely needed otherwise.
sealClass
:Seal the current definition of the specified class, to prevent further changes, by setting the corresponding slot in the class definition. This is rarely used, since classes in loaded packages are sealed by locking their namespace.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Chapter 9 has some details not in the later reference.)
getClass
,
Classes_Details
,
Methods_Details
,
makeClassRepresentation
The function findMethods
converts the methods defined in a table for a generic
function (as used for selection of methods) into a list, for study or
display. The list is actually from the class listOfMethods
(see the section describing the class, below).
The list will be limited
to the methods defined in environment where
if that argument is
supplied and limited to those including one or more of the
specified classes
in the method signature if that argument is
supplied.
To see the actual table (an environment
) used
for methods dispatch, call getMethodsForDispatch
.
The names of the list returned by findMethods
are the names of
the objects in the table.
The function findMethodSignatures
returns a character matrix
whose rows are the class names from the signature of the corresponding
methods; it operates either from a list returned by
findMethods
, or by computing such a list itself, given the same
arguments as findMethods
.
The function hasMethods
returns TRUE
or FALSE
according to whether there is a non-empty table of methods for
function f
in the environment or search position where
(or for the generic function generally if where
is missing).
The defunct function getMethods
is an older alternative to
findMethods
, returning information in the form of an object of
class MethodsList
, previously used for method dispatch. This
class of objects is deprecated generally and will disappear in a
future version of R.
findMethods(f, where, classes = character(), inherited = FALSE, package = "") findMethodSignatures(..., target = TRUE, methods = ) hasMethods(f, where, package) ## Deprecated in 2010 and defunct in 2015 for 'table = FALSE': getMethods(f, where, table = FALSE)
findMethods(f, where, classes = character(), inherited = FALSE, package = "") findMethodSignatures(..., target = TRUE, methods = ) hasMethods(f, where, package) ## Deprecated in 2010 and defunct in 2015 for 'table = FALSE': getMethods(f, where, table = FALSE)
f |
A generic function or the character-string name of one. |
where |
Optionally, an environment or position on the search list to look for methods metadata. If |
table |
If |
classes |
If supplied, only methods whose signatures contain at least one of the supplied classes will be included in the value returned. |
inherited |
Logical flag; if |
... |
In the call to |
target |
Optional flag to |
methods |
In the call to |
package |
In a call to |
The functions obtain a table of the defined methods, either from the
generic function or from the stored metadata object in the environment
specified by where
. In a call to getMethods
, the information in the table is converted
as described above to produce the returned value, except with the
table
argument.
Note that hasMethods
, but not the other functions, can be used
even if no generic function of this name is currently found. In this
case package
must either be supplied as an argument or included
as an attribute of f
, since the package name is part of the
identification of the methods tables.
The class "listOfMethods"
returns the methods as a named list
of method definitions (or a primitive function, see the slot
documentation below). The names
are the strings used to store the corresponding objects in the
environment from which method dispatch is computed.
The current implementation uses the names of the corresponding classes
in the method signature, separated by "#"
if more than one
argument is involved in the signature.
.Data
:Object of class "list"
The method
definitions.
Note that these may include the primitive function
itself as default method,
when the generic corresponds to a primitive. (Basically, because
primitive functions are abnormal R objects, which cannot currently be
extended as method definitions.) Computations that use the returned
list to derive other information need to take account of this
possibility. See the implementation of findMethodSignatures
for an example.
arguments
:Object of class "character"
. The
names of the formal arguments in the signature of the generic function.
signatures
:Object of class "list"
. A list of
the signatures of the individual methods. This is currently the
result of splitting the names
according to the "#"
separator.
If the object has been constructed from a table, as when returned by
findMethods
, the signatures will all have the same length.
However, a list rather than a character matrix is used for
generality. Calling findMethodSignatures
as in the example
below will always convert to the matrix form.
generic
:Object of class "genericFunction"
.
The generic function corresponding to these methods. There
are plans to generalize this slot to allow reference to the function.
names
:Object of class "character"
. The
names as noted are the class names separated by "#"
.
Class "namedList"
, directly.
Class "list"
, by class "namedList"
, distance 2.
Class "vector"
, by class "namedList"
, distance 3.
showMethods
, selectMethod
, Methods_Details
mm <- findMethods("Ops") findMethodSignatures(methods = mm)
mm <- findMethods("Ops") findMethodSignatures(methods = mm)
Beginning with R version 1.8.0, the class of an object contains the
identification of the package in which the class is defined. The
function fixPre1.8
fixes and re-assigns objects missing that information
(typically because they were loaded from a file saved with a previous
version of R.)
fixPre1.8(names, where)
fixPre1.8(names, where)
names |
Character vector of the names of all the objects to be fixed and re-assigned. |
where |
The environment from which to look for the objects, and
for class definitions. Defaults to the top environment of the
call to |
The named object will be saved where it was found. Its class attribute will be changed to the full form required by R 1.8; otherwise, the contents of the object should be unchanged.
Objects will be fixed and re-assigned only if all the following conditions hold:
The named object exists.
It is from a defined class (not a basic datatype which has no actual class attribute).
The object appears to be from an earlier version of R.
The class is currently defined.
The object is consistent with the current class definition.
If any condition except the second fails, a warning message is generated.
Note that fixPre1.8
currently fixes only the change in
class attributes. In particular, it will not fix binary versions of
packages installed with earlier versions of R if these use
incompatible features. Such packages must be re-installed from
source, which is the wise approach always when major version changes
occur in R.
The names of all the objects that were in fact re-assigned.
Generic functions (objects from or extending class
genericFunction
) are extended function objects,
containing information used in creating and dispatching methods for
this function. They also identify the package associated with the
function and its methods.
Generic functions are created and assigned by
setGeneric
or setGroupGeneric
and, indirectly, by
setMethod
.
As you might expect setGeneric
and
setGroupGeneric
create objects of class
"genericFunction"
and "groupGenericFunction"
respectively.
.Data
:Object of class "function"
, the
function definition of the generic, usually created
automatically as a call to standardGeneric
.
generic
:Object of class "character"
, the
name of the generic function.
package
:Object of class "character"
, the
name of the package to which the function definition belongs
(and not necessarily where the generic function is
stored). If the package is not specified explicitly in the
call to setGeneric
, it is usually the package on which
the corresponding non-generic function exists.
group
:Object of class "list"
, the group or
groups to which this generic function belongs. Empty by default.
valueClass
:Object of class "character"
; if
not an empty character vector, identifies one or more classes. It is
asserted that all methods for this function return objects
from these class (or from classes that extend them).
signature
:Object of class "character"
, the
vector of formal argument names that can appear in the
signature of methods for this generic function. By default,
it is all the formal arguments, except for .... Order
matters for efficiency: the most commonly used arguments in
specifying methods should come first.
default
:Object of class "optionalMethod"
(a union of classes "function"
and "NULL"
), containing
the default method for this function if any. Generated
automatically and used to initialize method dispatch.
skeleton
:Object of class "call"
, a slot used
internally in method dispatch. Don't expect to use it
directly.
Class "function"
, from data part.
Class "OptionalMethods"
, by class "function"
.
Class "PossibleMethod"
, by class "function"
.
Generic function objects are used in the creation and dispatch of formal methods; information from the object is used to create methods list objects and to merge or update the existing methods for this generic.
The functions documented here manage collections of methods associated with a generic function, as well as providing information about the generic functions themselves.
isGeneric(f, where, fdef, getName = FALSE) isGroup(f, where, fdef) removeGeneric(f, where) dumpMethod(f, signature, file, where, def) findFunction(f, generic = TRUE, where = topenv(parent.frame())) dumpMethods(f, file, signature, methods, where) signature(...) removeMethods(f, where = topenv(parent.frame()), all = missing(where)) setReplaceMethod(f, ..., where = topenv(parent.frame())) getGenerics(where, searchForm = FALSE)
isGeneric(f, where, fdef, getName = FALSE) isGroup(f, where, fdef) removeGeneric(f, where) dumpMethod(f, signature, file, where, def) findFunction(f, generic = TRUE, where = topenv(parent.frame())) dumpMethods(f, file, signature, methods, where) signature(...) removeMethods(f, where = topenv(parent.frame()), all = missing(where)) setReplaceMethod(f, ..., where = topenv(parent.frame())) getGenerics(where, searchForm = FALSE)
f |
The character string naming the function. |
where |
The environment, namespace, or search-list position from which to search for objects. By default, start at the top-level environment of the calling function, typically the global environment (i.e., use the search list), or the namespace of a package from which the call came. It is important to supply this argument when calling any of these functions indirectly. With package namespaces, the default is likely to be wrong in such calls. |
signature |
The class signature of the relevant method. A
signature is a named or unnamed vector of character strings. If
named, the names must be formal argument names for the generic
function. Signatures are matched to the arguments specified in
the signature slot of the generic function (see the Details
section of the The |
file |
The file or connection on which to dump method definitions. |
def |
The function object defining the method; if omitted, the current method definition corresponding to the signature. |
... |
Named or unnamed arguments to form a signature. |
generic |
In testing or finding functions, should generic
functions be included. Supply as |
fdef |
Optional, the generic function definition. Usually omitted in calls to |
getName |
If |
methods |
The methods object containing the methods to be dumped. By default,
the methods defined for this generic (optionally on the specified
|
all |
in |
searchForm |
In |
isGeneric
:Is there a function named f
, and if so, is it a generic?
The getName
argument allows a function to find the name
from a function definition. If it is TRUE
then the name of
the generic is returned, or FALSE
if this is not a generic
function definition.
The behavior of isGeneric
and getGeneric
for
primitive functions is slightly different. These functions don't
exist as formal function objects (for efficiency and historical
reasons), regardless of whether methods have been defined for
them. A call to isGeneric
tells you whether methods have
been defined for this primitive function, anywhere in the current
search list, or in the specified position where
. In
contrast, a call to getGeneric
will return what the
generic for that function would be, even if no methods have been
currently defined for it.
removeGeneric
, removeMethods
:Remove all the methods for the generic function of this
name. In addition, removeGeneric
removes the function
itself; removeMethods
restores the non-generic function
which was the default method. If there was no default method,
removeMethods
leaves a generic function with no methods.
standardGeneric
:Dispatches a method from the current function call for the generic
function f
. It is an error to call
standardGeneric
anywhere except in the body of the
corresponding generic function.
Note that standardGeneric
is a primitive function in
the base package
for efficiency
reasons, but rather documented here where it belongs naturally.
dumpMethod
:Dump the method for this generic function and signature.
findFunction
:return a list of either the positions on the search list, or the
current top-level environment, on which a function object
for name
exists. The returned value is always a
list, use the first element to access the first visible version
of the function. See the example.
NOTE: Use this rather than find
with
mode="function"
, which is not as meaningful, and has a few
subtle bugs from its use of regular expressions. Also,
findFunction
works correctly in the code for a package
when attaching the package via a call to library
.
dumpMethods
:Dump all the methods for this generic.
signature
:Returns a named list of classes to be matched to arguments of a generic function.
getGenerics
:returns the names of the generic
functions that have methods defined on where
; this
argument can be an environment or an index into the search
list. By default, the whole search list is used.
The methods definitions are stored with
package qualifiers; for example, methods for function
"initialize"
might refer to two different functions
of that name, on different packages. The package names
corresponding to the method list object are contained in the
slot package
of the returned object. The form of
the returned name can be plain (e.g., "base"
), or in
the form used in the search list ("package:base"
)
according to the value of searchForm
isGeneric
:If the fdef
argument is supplied, take this as the
definition of the generic, and test whether it is really a
generic, with f
as the name of the generic. (This argument
is not available in S-Plus.)
removeGeneric
:If where
supplied, just remove the version on this element
of the search list; otherwise, removes the first version
encountered.
standardGeneric
:Generic functions should usually have a call to
standardGeneric
as their entire body. They can, however,
do any other computations as well.
The usual setGeneric
(directly or through calling
setMethod
) creates a function with a call to
standardGeneric
.
dumpMethod
:The resulting source file will recreate the method.
findFunction
:If generic
is FALSE
, ignore generic functions.
dumpMethods
:If signature
is supplied only the methods matching this
initial signature are dumped. (This feature is not found in
S-Plus: don't use it if you want compatibility.)
signature
:The advantage of using signature
is to provide a check on
which arguments you meant, as well as clearer documentation in
your method specification. In addition, signature
checks
that each of the elements is a single character string.
removeMethods
:Returns TRUE
if f
was a generic function,
FALSE
(silently) otherwise.
If there is a default method, the function will be re-assigned as
a simple function with this definition.
Otherwise, the generic function remains but with no methods (so
any call to it will generate an error). In either case, a
following call to setMethod
will consistently
re-establish the same generic function as before.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
getMethod
(also for selectMethod
),
setGeneric
,
setClass
,
showMethods
require(stats) # for lm ## get the function "myFun" -- throw an error if 0 or > 1 versions visible: findFuncStrict <- function(fName) { allF <- findFunction(fName) if(length(allF) == 0) stop("No versions of ",fName," visible") else if(length(allF) > 1) stop(fName," is ambiguous: ", length(allF), " versions") else get(fName, allF[[1]]) } try(findFuncStrict("myFun"))# Error: no version lm <- function(x) x+1 try(findFuncStrict("lm"))# Error: 2 versions findFuncStrict("findFuncStrict")# just 1 version rm(lm) ## method dumping ------------------------------------ setClass("A", slots = c(a="numeric")) setMethod("plot", "A", function(x,y,...){ cat("A meth\n") }) dumpMethod("plot","A", file="") ## Not run: setMethod("plot", "A", function (x, y, ...) { cat("AAAAA\n") } ) ## End(Not run) tmp <- tempfile() dumpMethod("plot","A", file=tmp) ## now remove, and see if we can parse the dump stopifnot(removeMethod("plot", "A")) source(tmp) stopifnot(is(getMethod("plot", "A"), "MethodDefinition")) ## same with dumpMethods() : setClass("B", contains="A") setMethod("plot", "B", function(x,y,...){ cat("B ...\n") }) dumpMethods("plot", file=tmp) stopifnot(removeMethod("plot", "A"), removeMethod("plot", "B")) source(tmp) stopifnot(is(getMethod("plot", "A"), "MethodDefinition"), is(getMethod("plot", "B"), "MethodDefinition"))
require(stats) # for lm ## get the function "myFun" -- throw an error if 0 or > 1 versions visible: findFuncStrict <- function(fName) { allF <- findFunction(fName) if(length(allF) == 0) stop("No versions of ",fName," visible") else if(length(allF) > 1) stop(fName," is ambiguous: ", length(allF), " versions") else get(fName, allF[[1]]) } try(findFuncStrict("myFun"))# Error: no version lm <- function(x) x+1 try(findFuncStrict("lm"))# Error: 2 versions findFuncStrict("findFuncStrict")# just 1 version rm(lm) ## method dumping ------------------------------------ setClass("A", slots = c(a="numeric")) setMethod("plot", "A", function(x,y,...){ cat("A meth\n") }) dumpMethod("plot","A", file="") ## Not run: setMethod("plot", "A", function (x, y, ...) { cat("AAAAA\n") } ) ## End(Not run) tmp <- tempfile() dumpMethod("plot","A", file=tmp) ## now remove, and see if we can parse the dump stopifnot(removeMethod("plot", "A")) source(tmp) stopifnot(is(getMethod("plot", "A"), "MethodDefinition")) ## same with dumpMethods() : setClass("B", contains="A") setMethod("plot", "B", function(x,y,...){ cat("B ...\n") }) dumpMethods("plot", file=tmp) stopifnot(removeMethod("plot", "A"), removeMethod("plot", "B")) source(tmp) stopifnot(is(getMethod("plot", "A"), "MethodDefinition"), is(getMethod("plot", "B"), "MethodDefinition"))
Get the definition of a class.
getClass (Class, .Force = FALSE, where) getClassDef(Class, where, package, inherits = TRUE)
getClass (Class, .Force = FALSE, where) getClassDef(Class, where, package, inherits = TRUE)
Class |
the character-string name of the class, often with a
|
.Force |
if |
where |
environment from which to begin the search for the definition; by default, start at the top-level (global) environment and proceed through the search list. |
package |
the name or environment of the package asserted to hold the
definition. If it is a non-empty string it is used instead of
|
inherits |
logical; should the class definition be retrieved from
any enclosing environment and also from the cache? If |
Class definitions are stored in metadata objects in a package
namespace or other environment where they are defined. When
packages are loaded, the class definitions in the package are cached in an internal
table. Therefore, most calls to getClassDef
will find the
class in the cache or fail to find it at all, unless inherits
is FALSE
, in which case only the environment(s) defined by
package
or where
are searched.
The class cache allows for multiple definitions of the same class name in separate environments, with of course the limitation that the package attribute or package name must be provided in the call to
The object defining the class. If the class definition is not found,
getClassDef
returns NULL
, while getClass
, which
calls getClassDef
, either generates an error or, if
.Force
is TRUE
, returns a simple definition for the
class. The latter case is used internally, but is not typically
sensible in user code.
The non-null returned value is an object of class
classRepresentation
.
Use functions such as setClass
and
setClassUnion
to create class definitions.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
classRepresentation,
setClass
,
isClass
.
getClass("numeric") ## a built in class cld <- getClass("thisIsAnUndefinedClass", .Force = TRUE) cld ## a NULL prototype ## If you are really curious: utils::str(cld) ## Whereas these generate errors: try(getClass("thisIsAnUndefinedClass")) try(getClassDef("thisIsAnUndefinedClass"))
getClass("numeric") ## a built in class cld <- getClass("thisIsAnUndefinedClass", .Force = TRUE) cld ## a NULL prototype ## If you are really curious: utils::str(cld) ## Whereas these generate errors: try(getClass("thisIsAnUndefinedClass")) try(getClassDef("thisIsAnUndefinedClass"))
The function selectMethod()
returns the method that
would be selected for a call to function f
if the arguments had
classes as specified by signature
. Failing to find a method
is an error, unless argument optional = TRUE
, in which case
NULL
is returned.
The function findMethod()
returns a list of
environments that contain a method for the specified function and signature; by
default, these are a subset of the packages in the current search
list. See section “Using findMethod()
” for details.
The function getMethod()
returns the method corresponding to the
function and signature supplied similarly to selectMethod
, but
without using inheritance or group generics.
The functions hasMethod()
and
existsMethod()
test whether selectMethod()
or
getMethod()
, respectively, finds a matching method.
selectMethod(f, signature, optional = FALSE, useInherited =, mlist = , fdef = , verbose = , doCache = ) findMethod(f, signature, where) getMethod(f, signature = character(), where, optional = FALSE, mlist, fdef) existsMethod(f, signature = character(), where) hasMethod(f, signature = character(), where)
selectMethod(f, signature, optional = FALSE, useInherited =, mlist = , fdef = , verbose = , doCache = ) findMethod(f, signature, where) getMethod(f, signature = character(), where, optional = FALSE, mlist, fdef) existsMethod(f, signature = character(), where) hasMethod(f, signature = character(), where)
f |
a generic function or the character-string name of one. |
signature |
the signature of classes to match to the arguments
of |
where |
the environment in which to look for the
method(s). By default, if the call comes from the command line, the table of methods defined in the generic
function itself is used, except for |
optional |
if the selection in |
mlist , fdef , useInherited , verbose , doCache
|
optional arguments
to |
The signature
argument specifies classes, corresponding to
formal arguments of the generic function; to be precise, to the
signature
slot of the generic function object. The argument
may be a vector of strings identifying classes, and may be named or
not. Names, if supplied, match the names of those formal arguments
included in the signature of the generic. That signature is normally
all the arguments except .... However, generic functions can be
specified with only a subset of the arguments permitted, or with the
signature taking the arguments in a different order.
It's a good idea to name the arguments in the signature to avoid
confusion, if you're dealing with a generic that does something
special with its signature. In any case, the elements of the
signature are matched to the formal signature by the same rules used
in matching arguments in function calls (see
match.call
).
The strings in the signature may be class names, "missing"
or
"ANY"
. See Methods_Details for the meaning of these in method
selection. Arguments not supplied in the signature implicitly
correspond to class "ANY"
; in particular, giving an empty
signature means to look for the default method.
A call to getMethod
returns the method for a particular
function and signature. The search for the method makes no use of
inheritance.
The function selectMethod
also looks for a method given the
function and signature, but makes full use of the method dispatch
mechanism; i.e., inherited methods and group generics are taken into
account just as they would be in dispatching a method for the
corresponding signature, with the one exception that conditional
inheritance is not used. Like getMethod
, selectMethod
returns NULL
or generates an error if
the method is not found, depending on the argument optional
.
Both selectMethod
and getMethod
will normally use the
current version of the generic function in the R session, which has a
table of the methods obtained from all the packages loaded in the
session. Optional arguments can cause a search for the generic function from a
specified environment, but this is rarely a useful idea. In contrast,
findMethod
has a different default and the optional
where=
argument may be needed. See the section “Using
findMethod()
”.
The functions existsMethod
and hasMethod
return
TRUE
or FALSE
according to whether a method is found,
the first corresponding to getMethod
(no inheritance) and the
second to selectMethod
.
The call to selectMethod
or getMethod
returns the selected method, if
one is found.
(This class extends function
, so you can use the result
directly as a function if that is what you want.)
Otherwise an error is thrown if optional
is FALSE
and NULL
is returned if
optional
is TRUE
.
The returned method object is a
MethodDefinition
object, except that the default method for a primitive function is required to be the primitive itself.
Note therefore that the only reliable test that the search failed is
is.null()
.
The returned value of findMethod
is a list of
environments in which a corresponding method was found; that is, a
table of methods including the one specified.
findMethod()
As its name suggests, this function is intended to behave like
find
, which produces a list of the packages on the
current search list which have, and have exported, the object named.
That's what findMethod
does also, by default. The
“exported” part in this case means that the package's namespace
has an exportMethods
directive for this generic function.
An important distinction is that the absence of such a directive does not prevent methods from the package from being called once the package is loaded. Otherwise, the code in the package could not use un-exported methods.
So, if your question is whether loading package thisPkg
will define a
method for this function and signature, you need to ask that question
about the namespace of the package:
findMethod(f, signature, where = asNamespace("thisPkg"))
If the package did not export the method, attaching it and calling
findMethod
with no where
argument will not find the
method.
Notice also that the length of the signature must be what the
corresponding package used. If thisPkg
had only methods for
one argument, only length-1 signatures will match (no trailing
"ANY"
), even if another currently loaded package had signatures
with more arguments.
as()
The function setAs
allows packages to define methods for
coercing one class of objects to another class. This works internally
by defining methods for the generic function coerce(from,
to)
,
which can not be called directly.
The R evaluator selects
methods for this purpose using a different form of inheritance. While
methods can be inherited for the object being coerced, they cannot
inherit for the target class, since the result would not be a valid
object from that class.
If you want to
examine the selection procedure, you must supply the optional argument
useInherited = c(TRUE, FALSE)
to selectMethod
.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.6 for some details of method selection.)
Methods_Details
for the details of method
selection; GenericFunctions
for other functions
manipulating methods and generic function objects;
MethodDefinition
for the class that represents
method definitions.
testFun <- function(x)x setGeneric("testFun") setMethod("testFun", "numeric", function(x)x+1) hasMethod("testFun", "numeric") # TRUE hasMethod("testFun", "integer") #TRUE, inherited existsMethod("testFun", "integer") #FALSE hasMethod("testFun") # TRUE, default method hasMethod("testFun", "ANY")
testFun <- function(x)x setGeneric("testFun") setMethod("testFun", "numeric", function(x)x+1) hasMethod("testFun", "numeric") # TRUE hasMethod("testFun", "integer") #TRUE, inherited existsMethod("testFun", "integer") #FALSE hasMethod("testFun") # TRUE, default method hasMethod("testFun", "ANY")
The functions below produce the package associated with a particular environment or position on the search list, or of the package containing a particular function. They are primarily used to support computations that need to differentiate objects on multiple packages.
getPackageName(where, create = TRUE) setPackageName(pkg, env) packageSlot(object) packageSlot(object) <- value
getPackageName(where, create = TRUE) setPackageName(pkg, env) packageSlot(object) packageSlot(object) <- value
where |
the environment or position on the search list associated with the desired package. |
object |
object providing a character string name, plus the package in which this object is to be found. |
value |
the name of the package. |
create |
flag, should a package name be created if none can be
inferred? If |
pkg , env
|
make the string in |
Package names are normally installed during loading of the package,
by the INSTALL script or by the library
function. (Currently, the name is stored as the object
.packageName
but don't trust this for the future.)
getPackageName
returns the character-string name of the package
(without the extraneous "package:"
found in the search list).
packageSlot
returns or sets the package name slot (currently
an attribute, not a formal slot, but this may change someday).
setPackageName
can be used to establish a package name in an
environment that would otherwise not have one. This
allows you to create classes and/or methods in an arbitrary
environment, but it is usually preferable to create packages by the
standard R programming tools (package.skeleton
, etc.)
## all the following usually return "base" getPackageName(length(search())) getPackageName(baseenv()) getPackageName(asNamespace("base")) getPackageName("package:base")
## all the following usually return "base" getPackageName(length(search())) getPackageName(baseenv()) getPackageName(asNamespace("base")) getPackageName("package:base")
Returns TRUE
if name
corresponds to an argument in the
call, either a formal argument to the function, or a component of
...
, and FALSE
otherwise.
hasArg(name)
hasArg(name)
name |
The name of a potential argument, as an unquoted name or character string. |
The expression hasArg(x)
, for example, is similar to
!missing(x)
, with two exceptions. First, hasArg
will look for
an argument named x
in the call if x
is not a formal
argument to the calling function, but ...
is. Second,
hasArg
never generates an error if given a name as an argument,
whereas missing(x)
generates an error if x
is not a
formal argument.
Always TRUE
or FALSE
as described above.
ftest <- function(x1, ...) c(hasArg(x1), hasArg("y2")) ftest(1) ## c(TRUE, FALSE) ftest(1, 2) ## c(TRUE, FALSE) ftest(y2 = 2) ## c(FALSE, TRUE) ftest(y = 2) ## c(FALSE, FALSE) (no partial matching) ftest(y2 = 2, x = 1) ## c(TRUE, TRUE) partial match x1
ftest <- function(x1, ...) c(hasArg(x1), hasArg("y2")) ftest(1) ## c(TRUE, FALSE) ftest(1, 2) ## c(TRUE, FALSE) ftest(y2 = 2) ## c(FALSE, TRUE) ftest(y = 2) ## c(FALSE, FALSE) (no partial matching) ftest(y2 = 2, x = 1) ## c(TRUE, TRUE) partial match x1
The implicit generic mechanism stores generic versions of functions in a table in a package. The package does not want the current version of the function to be a generic, however, and retains the non-generic version.
When a call to setMethod
or
setGeneric
creates a generic version for one of these
functions, the object in the table is used.
This mechanism is only needed if special arguments were used to
create the generic; e.g., the signature
or the valueClass
options.
Function implicitGeneric()
returns the implicit
generic version, setGenericImplicit()
turns a generic implicit,
prohibitGeneric()
prevents your function from being made
generic, and registerImplicitGenerics()
saves a set of implicit
generic definitions in the cached table of the current session.
implicitGeneric(name, where, generic) setGenericImplicit(name, where, restore = TRUE) prohibitGeneric(name, where) registerImplicitGenerics(what, where)
implicitGeneric(name, where, generic) setGenericImplicit(name, where, restore = TRUE) prohibitGeneric(name, where) registerImplicitGenerics(what, where)
name |
Character string name of the function. |
where |
Package or environment in which to register the implicit generics. When using the functions from the top level of your own package source, this argument should be omitted. |
generic |
Obsolete, and likely to be deprecated. |
restore |
Should the non-generic version of the function be restored?. |
what |
Optional table of the implicit generics to register, but nearly always omitted, when it defaults to a standard metadata name. |
Multiple packages may define methods for the same function, to apply
to classes defined in that package. Arithmetic and other operators,
plot()
and many other basic computations are typical
examples. It's essential that all such packages write methods for
the same definition of the generic function. So long as that
generic uses the default choice for signature and other parameters,
nothing needs to be done.
If the generic has special properties, these need to be ensured for
all packages creating methods for it. The simplest solution is just
to make the function generic in the package that originally owned
it. If for some reason the owner(s) of that package are unwilling
to do this, the alternative is to define the correct generic,
save it in a special table and restore the non-generic version by
calling setGenericImplicit
.
Note that the package containing the function can define methods for the implicit generic as well; when the implicit generic is made a real generic, those methods will be included.
The usual reason for having a
non-default implicit generic is to provide a non-default signature,
and the usual reason for that is to allow lazy evaluation of
some arguments. All arguments in the signature of a
generic function must be evaluated at the time the function needs to
select a method.
In the base function with()
in the example below, evaluation of the argument
expr
must be delayed; therefore, it is excluded from the signature.
If you want to completely prohibit anyone from turning your function
into a generic, call prohibitGeneric()
.
Function implicitGeneric()
returns the implicit generic
version of the named function. If there is no table of these or if
this function is not in the table, the result of a simple call
setGeneric(name)
is returned.
Function implicitGeneric()
returns the implicit generic
definition (and caches that definition the first time if it has to
construct it).
The other functions exist for their side effect and return nothing useful.
Implicit generic versions exist for some functions in the packages supplied in the distribution of R itself. These are stored in the ‘methods’ package itself and will always be available.
As emphasized repeatedly in the documentation,
setGeneric()
calls for a function in another package
should never have non-default settings for arguments such as
signature
.
The reasoning applies specially to functions in supplied packages,
since methods for these are likely to exist in multiple packages.
A call to implicitGeneric()
will show the generic version.
### How we would make the function with() into a generic: ## Since the second argument, 'expr' is used literally, we want ## with() to only have "data" in the signature. ## Not run: setGeneric("with", signature = "data") ## Now we could predefine methods for "with" if we wanted to. ## When ready, we store the generic as implicit, and restore the original setGenericImplicit("with") ## End(Not run) implicitGeneric("with") # (This implicit generic is stored in the 'methods' package.)
### How we would make the function with() into a generic: ## Since the second argument, 'expr' is used literally, we want ## with() to only have "data" in the signature. ## Not run: setGeneric("with", signature = "data") ## Now we could predefine methods for "with" if we wanted to. ## When ready, we store the generic as implicit, and restore the original setGenericImplicit("with") ## End(Not run) implicitGeneric("with") # (This implicit generic is stored in the 'methods' package.)
For a class (or class definition, see getClass
and
the description of class classRepresentation
),
give the names which are inherited from “above”, i.e., super
classes, rather than by this class' definition itself.
inheritedSlotNames(Class, where = topenv(parent.frame()))
inheritedSlotNames(Class, where = topenv(parent.frame()))
Class |
character string or
|
where |
character vector of slot names, or NULL
.
slotNames
, slot
, setClass
, etc.
.srch <- search() library(stats4) inheritedSlotNames("mle") if(require("Matrix", quietly = TRUE)) withAutoprint({ inheritedSlotNames("Matrix") # NULL ## whereas inheritedSlotNames("sparseMatrix") # --> Dim & Dimnames ## i.e. inherited from "Matrix" class cl <- getClass("dgCMatrix") # six slots, etc inheritedSlotNames(cl) # *all* six slots are inherited }) ## Not run: ## detach package we've attached above: for(n in rev(which(is.na(match(search(), .srch))))) try( detach(pos = n) ) ## End(Not run)
.srch <- search() library(stats4) inheritedSlotNames("mle") if(require("Matrix", quietly = TRUE)) withAutoprint({ inheritedSlotNames("Matrix") # NULL ## whereas inheritedSlotNames("sparseMatrix") # --> Dim & Dimnames ## i.e. inherited from "Matrix" class cl <- getClass("dgCMatrix") # six slots, etc inheritedSlotNames(cl) # *all* six slots are inherited }) ## Not run: ## detach package we've attached above: for(n in rev(which(is.na(match(search(), .srch))))) try( detach(pos = n) ) ## End(Not run)
The arguments to function new
to create an object from a
particular class can be interpreted specially for that class, by the
definition of a method for function initialize
for the class.
This documentation describes some existing methods, and also outlines
how to write new ones.
signature(.Object = "ANY")
The default method for initialize
takes either named or
unnamed arguments. Argument names must be the names of slots in
this class definition, and the corresponding arguments must be
valid objects for the slot (that is, have the same class as
specified for the slot, or some superclass of that class). If the
object comes from a superclass, it is not coerced strictly, so
normally it will retain its current class (specifically,
as(object, Class, strict = FALSE)
).
Unnamed arguments must be objects of this class, of one of its superclasses, or one of its subclasses (from the class, from a class this class extends, or from a class that extends this class). If the object is from a superclass, this normally defines some of the slots in the object. If the object is from a subclass, the new object is that argument, coerced to the current class.
Unnamed arguments are processed first, in the order they appear. Then named arguments are processed. Therefore, explicit values for slots always override any values inferred from superclass or subclass arguments.
signature(.Object = "traceable")
Objects of a class that extends traceable
are used to
implement debug tracing (see class traceable and
trace
).
The initialize
method for these classes takes special
arguments def, tracer, exit, at, print
. The first of these
is the object to use as the original definition (e.g., a
function). The others correspond to the arguments to
trace
.
signature(.Object = "environment")
, signature(.Object = ".environment")
The initialize
method for environments takes a named list
of objects to be used to initialize the environment. Subclasses
of "environment"
inherit an initialize method through
".environment"
, which has the additional effect of
allocating a new environment. If you define your own method for
such a subclass, be sure either to call the existing method via
callNextMethod
or allocate an environment in your
method, since environments are references and are not duplicated
automatically.
signature(.Object = "signature")
This is a method for internal use only.
It takes an optional functionDef
argument to provide a
generic function with a signature
slot to define the
argument names. See Methods_Details for details.
Initialization methods provide a general mechanism corresponding to generator functions in other languages.
The arguments to initialize
are .Object
and
.... Nearly always, initialize
is called from new
,
not directly. The .Object
argument is then the
prototype object from the class.
Two techniques are often appropriate for initialize
methods:
special argument names and callNextMethod
.
You may want argument names that are more natural to your users than
the (default) slot names. These will be the formal arguments to
your method definition, in addition to .Object
(always) and
... (optionally). For example, the method for class
"traceable"
documented above would be created by a call to
setMethod
of the form:
setMethod("initialize", "traceable", function(.Object, def, tracer, exit, at, print) { .... } )
In this example, no other arguments are meaningful, and the resulting method will throw an error if other names are supplied.
When your new class extends another class, you may want to call the
initialize method for this superclass (either a special method or the
default). For example, suppose you want to define a method for your
class, with special argument x
, but you also want users to be
able to set slots specifically. If you want x
to override the
slot information, the beginning of your method definition might look
something like this:
function(.Object, x, ...) { Object <- callNextMethod(.Object, ...) if(!missing(x)) { # do something with x
You could also choose to have the inherited method override, by first
interpreting x
, and then calling the next method.
The majority of applications using methods and classes will be in R packages implementing new computations for an application, using new classes of objects that represent the data and results. Computations will be implemented using methods that implement functional computations when one or more of the arguments is an object from these classes.
Calls to the functions setClass()
define the new classes;
calls to setMethod
define the methods.
These, along with ordinary R computations, are sufficient to get
started for most applications.
Classes are defined in terms of the data in them and what other classes of data they inherit from. Section ‘Defining Classes’ outlines the basic design of new classes.
Methods are R functions, often implementing basic computations as they apply to the new classes of objects. Section ‘Defining Methods’ discusses basic requirements and special tools for defining methods.
The classes discussed here are the original functional classes. R also supports formal classes and methods similar to those in other languages such as Python, in which methods are part of class definitions and invoked on an object. These are more appropriate when computations expect references to objects that are persistent, making changes to the object over time. See ReferenceClasses and Chapter 9 of the reference for the choice between these and S4 classes.
All objects in R belong to a class; ordinary vectors and other basic
objects are built-in (builtin-class).
A new class is defined in terms of the named slots that is has
and/or in terms of existing classes that it inherits from, or
contains (discussed in ‘Class Inheritance’ below).
A call to setClass()
names a new class and uses the corresponding arguments to
define it.
For example, suppose we want a class of objects to represent a collection of positions, perhaps from GPS readings. A natural way to think of these in R would have vectors of numeric values for latitude, longitude and altitude. A class with three corresponding slots could be defined by:
Pos <- setClass("Pos", slots = c(latitude = "numeric",
longitude = "numeric", altitude = "numeric"))
The value returned is a function, typically assigned as here with the name of the class. Calling this function returns an object from the class; its arguments are named with the slot names. If a function in the class had read the corresponding data, perhaps from a CSV file or from a data base, it could return an object from the class by:
Pos(latitude = x, longitude = y, altitude = z)
The slots are accessed by the
@
operator; for example, if g
is an object from
the class, g@latitude
.
In addition to returning a generator function the call to
setClass()
assigns a definition of the class in a
special metadata object in the package's namespace.
When the package is loaded into an R session, the class definition is
added to a table of known classes.
To make the class and the generating function publicly available, the
package should include POS
in exportClasses()
and
export()
directives in its NAMESPACE
file:
exportClasses(Pos); export(Pos)
Defining methods for an R function makes that function generic. Instead of a call to the function always being carried out by the same method, there will be several alternatives. These are selected by matching the classes of the arguments in the call to a table in the generic function, indexed by classes for one or more formal arguments to the function, known as the signatures for the methods.
A method definition then specifies three things: the name of the function, the signature and the method definition itself. The definition must be a function with the same formal arguments as the generic.
For example, a method to make a plot of an object from class
"Pos"
could be defined by:
setMethod("plot", c("Pos", "missing"), function(x, y, ...) {
plotPos(x, y) })
This method will match a call to plot()
if the first
argument is from class "Pos"
or a subclass of that.
The second argument must be missing; only a missing argument matches
that class in the signature.
Any object will match class "ANY"
in the corresponding position
of the signature.
A class may inherit all the slots and methods of one or more existing
classes by specifying the names of the inherited classes in the contains =
argument to
setClass()
.
To define a class that extends class "Pos"
to a class
"GPS"
with a slot for the observation times:
GPS <- setClass("GPS", slots = c(time = "POSIXt"), contains = "Pos")
The inherited classes may be S4 classes, S3
classes or basic data types.
S3 classes need to be identified as such by a call to
setOldClass()
; most S3 classes in the base package and
many in the other built-in packages are already declared, as is
"POSIXt"
.
If it had not been, the application package should contain:
setOldClass("POSIXt")
Inheriting from one of the R types is special. Objects from the new
class will have the same type. A class
Currency
that contains numeric data plus a slot "unit"
would be created by
Currency <- setClass("Currency", slots = c(unit = "character"),
contains = "numeric")
Objects created from this class will have type "numeric"
and
inherit all the builtin arithmetic and other computations for that
type.
Classes can only inherit from at most one such type; if the class does
not inherit from a type, objects from the class will have type
"S4"
.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Functions to test inheritance relationships between an object and a
class or between two classes (extends
).
is(object, class2) extends(class1, class2, maybe = TRUE, fullInfo = FALSE)
is(object, class2) extends(class1, class2, maybe = TRUE, fullInfo = FALSE)
object |
any R object. |
class1 , class2
|
character strings giving the names of each of the two classes
between which |
fullInfo |
In a call to |
maybe |
What to return for conditional inheritance. But such relationships are rarely used and not recommended, so this argument should not be needed. |
A call to selectSuperClasses(cl)
returns a list of
superclasses, similarly to
extends(cl)
. Additional arguments restrict the class names
returned to direct superclasses and/or to non-virtual classes.
Either way, programming with the result, particularly using
sapply
, can be useful.
To find superclasses with more generally defined properties, one can program
with the result returned by extends
when called with one
class as argument.
By default, the call returns a character vector including the name of the class
itself and of all its superclasses.
Alternatively,
if extends
is called with fullInfo =
TRUE
, the return value is a named list, its names being the previous
character vector. The elements of the list corresponding to
superclasses are objects of class
SClassExtension
. Of the information in these objects, one piece can be useful:
the number of generations between the classes, given by the
"distance"
slot.
Programming with the result of the call to extends
, particularly using
sapply
, can select superclasses.
The programming technique is to define a test function that returns
TRUE
for superclasses or relationships obeying some
requirement. For example, to find only next-to-direct superclasses,
use this function with the list of extension objects:
function(what) is(what, "SClassExtension") && what@distance == 2
or, to find only superclasses from "myPkg"
, use this function
with the simple vector of names:
function(what) getClassDef(what)@package == "myPkg"
Giving such functions as an argument to sapply
called on the output of
extends
allows you to find
superclasses with desired properties. See the examples below.
Note that the function using extension objects must test the class of its argument since,
unfortunately for this purpose, the list returned by extends
includes
class1
itself, as the object TRUE
.
Prior to R 4.2.0 the code used the first elements of class1
and class2
, silently, These are now required to be length-one
character vectors.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Although inherits
is defined for S3 classes, it has
been modified so that the result returned is nearly always equivalent to
is
, both for S4 and non-S4 objects. Since it is implemented
in C, it is somewhat faster.
The only non-equivalences arise from use of setIs
,
which should rarely be encountered.
## Not run: ## this example can be run if package XRPython from CRAN is installed. supers <- extends("PythonInterface") ## find all the superclasses from package XR fromXR <- sapply(supers, function(what) getClassDef(what)@package == "XR") ## print them supers[fromXR] ## find all the superclasses at distance 2 superRelations <- extends("PythonInterface", fullInfo = TRUE) dist2 <- sapply(superRelations, function(what) is(what, "SClassExtension") && what@distance == 2) ## print them names(superRelations)[dist2] ## End(Not run)
## Not run: ## this example can be run if package XRPython from CRAN is installed. supers <- extends("PythonInterface") ## find all the superclasses from package XR fromXR <- sapply(supers, function(what) getClassDef(what)@package == "XR") ## print them supers[fromXR] ## find all the superclasses at distance 2 superRelations <- extends("PythonInterface", fullInfo = TRUE) dist2 <- sapply(superRelations, function(what) is(what, "SClassExtension") && what@distance == 2) ## print them names(superRelations)[dist2] ## End(Not run)
These functions check for either a method or a class that has been sealed when it was defined, and which therefore cannot be re-defined.
isSealedMethod(f, signature, fdef, where) isSealedClass(Class, where)
isSealedMethod(f, signature, fdef, where) isSealedClass(Class, where)
f |
The quoted name of the generic function. |
signature |
The class names in the method's signature, as
they would be supplied to |
fdef |
Optional, and usually omitted: the generic function
definition for |
Class |
The quoted name of the class. |
where |
where to search for the method or class definition. By
default, searches from the top environment of the call to
|
In the R implementation of classes and methods, it is possible to seal the definition of either a class or a method. The basic classes (numeric and other types of vectors, matrix and array data) are sealed. So also are the methods for the primitive functions on those data types. The effect is that programmers cannot re-define the meaning of these basic data types and computations. More precisely, for primitive functions that depend on only one data argument, methods cannot be specified for basic classes. For functions (such as the arithmetic operators) that depend on two arguments, methods can be specified if one of those arguments is a basic class, but not if both are.
Programmers can seal other class and method definitions by using the
sealed
argument to setClass
or setMethod
.
The functions return FALSE
if the method or class is not
sealed (including the case that it is not defined); TRUE
if
it is.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
## these are both TRUE isSealedMethod("+", c("numeric", "character")) isSealedClass("matrix") setClass("track", slots = c(x="numeric", y="numeric")) ## but this is FALSE isSealedClass("track") ## and so is this isSealedClass("A Name for an undefined Class") ## and so are these, because only one of the two arguments is basic isSealedMethod("+", c("track", "numeric")) isSealedMethod("+", c("numeric", "track"))
## these are both TRUE isSealedMethod("+", c("numeric", "character")) isSealedClass("matrix") setClass("track", slots = c(x="numeric", y="numeric")) ## but this is FALSE isSealedClass("track") ## and so is this isSealedClass("A Name for an undefined Class") ## and so are these, because only one of the two arguments is basic isSealedMethod("+", c("track", "numeric")) isSealedMethod("+", c("numeric", "track"))
The virtual class "language"
and the specific
classes that extend it represent unevaluated objects, as produced for
example by the parser or by functions such as quote
.
### each of these classes corresponds to an unevaluated object ### in the S language. ### The class name can appear in method signatures, ### and in a few other contexts (such as some calls to as()). "(" "<-" "call" "for" "if" "repeat" "while" "name" "{" ### Each of the classes above extends the virtual class "language"
### each of these classes corresponds to an unevaluated object ### in the S language. ### The class name can appear in method signatures, ### and in a few other contexts (such as some calls to as()). "(" "<-" "call" "for" "if" "repeat" "while" "name" "{" ### Each of the classes above extends the virtual class "language"
"language"
is a virtual class; no objects may be created from
it.
Objects from the other classes can be generated by a call to
new(Class, ...)
, where Class
is the quoted class name, and
the ... arguments are either empty or a single object that is
from this class (or an extension).
signature(from = "ANY", to = "call")
. A method
exists for as(object, "call")
, calling as.call()
.
showClass("language") is( quote(sin(x)) ) # "call" "language" (ff <- new("if")) ; is(ff) # "if" "language" (ff <- new("for")) ; is(ff) # "for" "language"
showClass("language") is( quote(sin(x)) ) # "call" "language" (ff <- new("if")) ; is(ff) # "if" "language" (ff <- new("for")) ; is(ff) # "for" "language"
"LinearMethodsList"
A version of methods lists that has been ‘linearized’
for producing summary information. The actual objects from class
"MethodsList"
used for method dispatch are defined recursively
over the arguments involved.
The function linearizeMlist
converts an ordinary methods
list object into the linearized form.
methods
:Object of class "list"
, the method
definitions.
arguments
:Object of class "list"
, the
corresponding formal arguments, namely as many of the arguments
in the signature of the generic function as are active in the
relevant method table.
classes
:Object of class "list"
, the
corresponding classes in the signatures.
generic
:Object of class "genericFunction"
;
the generic function to which the methods correspond.
The current version of linearizeMlist
does not take advantage of
the MethodDefinition
class, and therefore does more work for less
effect than it could. In particular, we may move to redefine both the
function and the class to take advantage of the stored signatures.
Don't write code depending precisely on the present form, although all
the current information will be obtainable in the future.
Function linearizeMlist
for the computation,
and class MethodsList
for the original, recursive
form.
Local reference classes are modified ReferenceClasses that isolate the objects to the local frame. Therefore, they do not propagate changes back to the calling environment. At the same time, they use the reference field semantics locally, avoiding the automatic duplication applied to standard R objects.
The current implementation has no special construction. To create a
local reference class, call setRefClass()
with a
contains=
argument that includes "localRefClass"
. See
the example below.
Local reference classes operate essentially as do regular, functional
classes in R; that is, changes are made by assignment and take place
in the local frame.
The essential difference is that replacement operations (like the
change to the twiddle
field in the example) do not cause
duplication of the entire object, as would be the case for a formal
class or for data with attributes or in a named list.
The purpose is to allow large objects in some fields that are not
changed along with potentially frequent changes to other fields, but
without copying the large fields.
setRefClass(Class, fields = , contains = c("localRefClass",....), methods =, where =, ...)
setRefClass(Class, fields = , contains = c("localRefClass",....), methods =, where =, ...)
Localization of objects is only partially automated in the current implementation.
Replacement expressions using the $<-
operator are safe.
However, if reference methods for the class themselves modify fields,
using <<-
, for example, then
one must ensure that the object is local to the relevant frame before
any such method is called.
Otherwise, standard reference class behavior still prevails.
There are two ways to ensure locality. The direct way is to invoke
the special
method x$ensureLocal()
on the object.
The other way is to modify a field explicitly by x$field <- ...
It's
only necessary that one or the other of these happens
once for each object, in order to trigger the shallow copy that
provides locality for the references. In the example below, we show
both mechanisms.
However it's done, localization must occur before any methods make changes. (Eventually, some use of code tools should at least largely automate this process, although it may be difficult to guarantee success under arbitrary circumstances.)
John Chambers
## class "myIter" has a BigData field for the real (big) data ## and a "twiddle" field for some parameters that it twiddles ## ( for some reason) myIter <- setRefClass("myIter", contains = "localRefClass", fields = list(BigData = "numeric", twiddle = "numeric")) tw <- rnorm(3) x1 <- myIter(BigData = rnorm(1000), twiddle = tw) # OK, not REALLY big twiddler <- function(x, n) { x$ensureLocal() # see the Details. Not really needed in this example for(i in seq_len(n)) { x$twiddle <- x$twiddle + rnorm(length(x$twiddle)) ## then do something .... ## Snooping in gdb, etc will show that x$BigData is not copied } return(x) } x2 <- twiddler(x1, 10) stopifnot(identical(x1$twiddle, tw), !identical(x1$twiddle, x2$twiddle))
## class "myIter" has a BigData field for the real (big) data ## and a "twiddle" field for some parameters that it twiddles ## ( for some reason) myIter <- setRefClass("myIter", contains = "localRefClass", fields = list(BigData = "numeric", twiddle = "numeric")) tw <- rnorm(3) x1 <- myIter(BigData = rnorm(1000), twiddle = tw) # OK, not REALLY big twiddler <- function(x, n) { x$ensureLocal() # see the Details. Not really needed in this example for(i in seq_len(n)) { x$twiddle <- x$twiddle + rnorm(length(x$twiddle)) ## then do something .... ## Snooping in gdb, etc will show that x$BigData is not copied } return(x) } x2 <- twiddler(x1, 10) stopifnot(identical(x1$twiddle, tw), !identical(x1$twiddle, x2$twiddle))
Constructs an object of class classRepresentation
to describe a particular class. Mostly a utility function, but you can
call it to create a class definition without assigning it, as
setClass
would do.
makeClassRepresentation(name, slots=list(), superClasses=character(), prototype=NULL, package, validity, access, version, sealed, virtual=NA, where)
makeClassRepresentation(name, slots=list(), superClasses=character(), prototype=NULL, package, validity, access, version, sealed, virtual=NA, where)
name |
character string name for the class |
slots |
named list of slot classes as would be supplied to
|
superClasses |
what classes does this class extend |
prototype |
an object providing the default data for the class,
e.g., the result of a call to |
package |
The character string name for the package in which
the class will be stored; see |
validity |
Optional validity method. See
|
access |
Access information. Not currently used. |
version |
Optional version key for version control. Currently generated, but not used. |
sealed |
Is the class sealed? See |
virtual |
Is this known to be a virtual class? |
where |
The environment from which to look for class definitions needed (e.g., for slots or superclasses). See the discussion of this argument under GenericFunctions. |
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
This function writes a source file containing a call to
setMethod
to define a method for the generic function
and signature supplied. By default the method definition is in line
in the call, but can be made an external (previously assigned) function.
method.skeleton(generic, signature, file, external = FALSE, where)
method.skeleton(generic, signature, file, external = FALSE, where)
generic |
the character string name of the generic function, or
the generic function itself. In the first case, the function
need not currently be a generic, as it would not for the
resulting call to |
signature |
the method signature, as it would be given to |
file |
a character string name for the output file, or a
writable connection. By default the generic function name and
the classes in the signature are concatenated, with separating
underscore characters. The file name should normally end in To write multiple method skeletons to one file, open the file
connection first and then pass it to |
external |
flag to control whether the function definition for
the method should be a separate external object assigned in the
source file, or included in line in the call to
|
where |
The environment in which to look for the function; by default,
the top-level environment of the call to |
The file
argument, invisibly, but the function is used for its side effect.
setClass("track", slots = c(x ="numeric", y="numeric")) method.skeleton("show", "track") ## writes show_track.R method.skeleton("Ops", c("track", "track")) ## writes "Ops_track_track.R" ## write multiple method skeletons to one file con <- file("./Math_track.R", "w") method.skeleton("Math", "track", con) method.skeleton("exp", "track", con) method.skeleton("log", "track", con) close(con)
setClass("track", slots = c(x ="numeric", y="numeric")) method.skeleton("show", "track") ## writes show_track.R method.skeleton("Ops", c("track", "track")) ## writes "Ops_track_track.R" ## write multiple method skeletons to one file con <- file("./Math_track.R", "w") method.skeleton("Math", "track", con) method.skeleton("exp", "track", con) method.skeleton("log", "track", con) close(con)
These classes extend the basic class "function"
when
functions are to be stored and used as method definitions.
Method definition objects are functions with additional information
defining how the function is being used as a method. The
target
slot is the class signature for which the method will
be dispatched, and the defined
slot the signature for which
the method was originally specified (that is, the one that appeared
in some call to setMethod
).
The action of setting a method by a call to setMethod
creates an object of this class. It's
unwise to create them directly.
The class "SealedMethodDefinition"
is created by a call to
setMethod
with argument sealed = TRUE
. It has
the same representation as "MethodDefinition"
.
.Data
:Object of class "function"
; the data
part of the definition.
target
:Object of class "signature"
; the
signature for which the method was wanted.
defined
:Object of class "signature"
; the
signature for which a method was found. If the method was
inherited, this will not be identical to target
.
generic
:Object of class "character"
; the function
for which the method was created.
Class "function"
, from data part.
Class "PossibleMethod"
, directly.
Class "OptionalMethods"
, by class "function"
.
class MethodsList
for the objects
defining sets of methods associated with a particular generic
function. The individual method definitions stored in these objects
are from class MethodDefinition
, or an extension.
Class MethodWithNext
for an extension used by
callNextMethod
.
You have navigated to an old link to documentation of S4 methods.
For basic use of classes and methods, see Introduction; to
create new method definitions, see setMethod
; for
technical details on S4 methods, see Methods_Details.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
This documentation covers some general topics on how methods work and how the methods package interacts with the rest of R. The information is usually not needed to get started with methods and classes, but may be helpful for moderately ambitious projects, or when something doesn't work as expected.
For additional information see documentation for
the important steps: (setMethod()
,
setClass()
and setGeneric()
). Also
Methods_for_Nongenerics
on defining formal methods for
functions that are not currently generic functions;
Methods_for_S3 for the relation to S3 classes and methods;
Classes_Details
for class definitions and
Chapters 9 and 10 of the reference.
A call to a generic function selects a method matching the actual arguments in the call. The body of the method is evaluated in the frame of the call to the generic function. A generic function is identified by its name and by the package to which it correspond. Unlike ordinary functions, the generic has a slot that specifies its package.
In an R session, there is one version of each such generic, regardless of where the call to that generic originated, and the generic function has a table of all the methods currently available for it; that is, all the methods in packages currently loaded into the session.
Methods are frequently defined for functions that are non-generic in
their original package,.
for example, for function plot()
in
package graphics.
An identical version of the corresponding generic function may exist
in several packages. All methods will be dispatched consistently
from the R session.
Each R package with a call to setMethod
in its source code
will include a methods metadata object for that generic.
When the package is loaded into an R session, the methods for each
generic function are cached, that is, added to the
environment of the generic function. This merged table of methods is used to
dispatch or select methods from the generic, using class inheritance
and possibly group generic functions (see
GroupGenericFunctions
) to find an applicable method.
See the “Method Selection and Dispatch” section below.
The caching computations ensure that only one version of each
generic function is visible globally; although different attached
packages may contain a copy of the generic function, these behave
identically with respect to method selection.
In contrast, it is possible for the same function name to refer to
more than one generic function, when these have different
package
slots. In the latter case, R considers the
functions unrelated: A generic function is defined by the
combination of name and package. See the “Generic Functions”
section below.
The methods for a generic are stored according to the
corresponding signature
in the call to setMethod
that defined the method. The signature associates one
class name with each of a subset of the formal arguments to the
generic function. Which formal arguments are available, and the
order in which they appear, are determined by the "signature"
slot of the generic function itself. By default, the signature of the
generic consists of all the formal arguments except ..., in the
order they appear in the function definition.
Trailing arguments in the signature of the generic will be inactive if no method has yet been specified that included those arguments in its signature. Inactive arguments are not needed or used in labeling the cached methods. (The distinction does not change which methods are dispatched, but ignoring inactive arguments improves the efficiency of dispatch.)
All arguments in the signature of the generic function will be evaluated when the
function is called, rather than using lazy
evaluation. Therefore, it's important to exclude
from the signature any arguments that need to be dealt with
symbolically (such as the expr
argument to function
with
). Note that only actual arguments are
evaluated, not default expressions.
A missing argument enters into the method selection as class
"missing"
.
The cached methods are stored in an environment object. The names used for assignment are a concatenation of the class names for the active arguments in the method signature.
When a call to a generic function is evaluated, a method is selected corresponding
to the classes of the actual arguments in the signature.
First, the cached methods table is searched for an exact match;
that is, a method stored under the signature defined by
the string value of class(x)
for each non-missing
argument, and "missing"
for each missing argument.
If no method is found directly for the actual arguments in a call to a
generic function, an attempt is made to match the available methods to
the arguments by using the superclass information about the actual
classes.
A method found by this search is cached
in the generic function so that future calls with the same argument classes will
not require repeating the search. In any likely application, the
search for inherited methods will be a negligible overhead.
Each class definition may include a list of one or more direct
superclasses of the new class.
The simplest and most common specification is by the contains=
argument in
the call to setClass
.
Each class named in this argument is a superclass of the new class.
A class will also have as a direct superclass any class union to which
it is a member.
Class unions are created by
a call to setClassUnion
.
Additional members can be added to the union by a simple call to
setIs
.
Superclasses specified by either mechanism are the direct superclasses.
Inheritance specified in either of these forms is simple in the
sense that all the information needed for the superclass is asserted
to be directly available from the object.
R inherited from S a more general form of inheritance in which
inheritance may require some transformation or be conditional on a
test.
This more general form has not proved to be useful in general
practical situations. Since it also adds some computational costs
non-simple inheritance is not recommended. See setIs
for the general version.
The direct superclasses themselves may
have direct superclasses and
similarly through further generations. Putting all this information together produces
the full list of superclasses for this class.
The superclass list is included in the definition of the class that is
cached during the R session.
The distance between the two classes is defined to be the
number of generations:
1
for direct superclasses (regardless of which mechanism
defined them), then 2
for the direct superclasses of those
classes, and so on.
To see all the superclasses, with their distance, print the class
definition by calling getClass
.
In addition, any class implicitly has class "ANY"
as a superclass. The
distance to "ANY"
is treated as larger than the distance to any
actual class.
The special class "missing"
corresponding to missing arguments
has only "ANY"
as a superclass, while "ANY"
has no
superclasses.
When a method is to be selected by inheritance, a search is made in
the table for all methods corresponding to a combination of
either the direct class or one of its superclasses, for each argument
in the active signature.
For an example, suppose there is only one argument in the signature and that the class of
the corresponding object was "dgeMatrix"
(from the recommended package
Matrix
).
This class has (currently) three direct superclasses and through these
additional superclasses at distances 2 through 4.
A method that had been defined for any of these classes or for class
"ANY"
(the default method) would be eligible.
Methods for the shortest difference are preferred.
If there is only one best method in this sense, method selection is unambiguous.
When there are multiple arguments in the signature, each argument will
generate a similar list of inherited classes.
The possible matches are now all the combinations of classes from each
argument (think of the function outer
generating an array of
all possible combinations).
The search now finds all the methods matching any of this combination
of classes.
For each argument, the distance to the superclass defines which
method(s) are preferred for that argument.
A method is considered best for selection if it is among the best
(i.e., has the least distance) for
each argument.
The end result is that zero, one or more methods may be “best”.
If one, this method is selected and cached in the table of methods.
If there is more than one best match, the selection is ambiguous and a message is
printed noting which method was selected (the first method
lexicographically in the ordering) and what other methods could have
been selected.
Since the ambiguity is usually nothing the end user could control,
this is not a warning.
Package authors should examine their package for possible ambiguous
inheritance by calling testInheritedMethods
.
Cached inherited selections are
not themselves used in future inheritance searches, since that could result
in invalid selections.
If you want inheritance computations to be done again (for example,
because a newly loaded package has a more direct method than one
that has already been used in this session), call
resetGeneric
. Because classes and methods involving
them tend to come from the same package, the current implementation
does not reset all generics every time a new package is loaded.
Besides being initiated through calls to the generic function, method
selection can be done explicitly by calling the function
selectMethod
.
Note that some computations may use this function directly, with
optional arguments.
The prime example is the use of coerce()
methods by
function as()
.
There has been some confusion from comparing coerce methods to a call
to selectMethod
with other options.
Once a method has been selected, the evaluator creates a new context
in which a call to the method is evaluated.
The context is initialized with the arguments from the call to the
generic function.
These arguments are not rematched. All the arguments in the signature
of the generic will have been evaluated (including any that are
currently inactive); arguments that are not in the signature will obey
the usual lazy evaluation rules of the language.
If an argument was missing in the call, its default expression if any
will not have been evaluated, since method dispatch always uses
class missing
for such arguments.
A call to a generic function therefore has two contexts: one for the function and a second for the method. The argument objects will be copied to the second context, but not any local objects created in a nonstandard generic function. The other important distinction is that the parent (“enclosing”) environment of the second context is the environment of the method as a function, so that all R programming techniques using such environments apply to method definitions as ordinary functions.
For further discussion of method selection and dispatch, see the references in the sections indicated.
In principle, a generic function could be any function that evaluates
a call to standardGeneric()
, the internal function that selects
a method and evaluates a call to the selected method. In practice,
generic functions are special objects that in addition to being from a
subclass of class "function"
also extend the class
genericFunction
. Such objects have slots to define
information needed to deal with their methods. They also have
specialized environments, containing the tables used in method
selection.
The slots "generic"
and "package"
in the object are the
character string names of the generic function itself and of the
package from which the function is defined.
As with classes, generic functions are uniquely defined in R by the
combination of the two names.
There can be generic functions of the same name associated with
different packages (although inevitably keeping such functions cleanly
distinguished is not always easy).
On the other hand, R will enforce that only one definition of a
generic function can be associated with a particular combination of
function and package name, in the current session or other active
version of R.
Tables of methods for a particular generic function, in this sense, will often be spread over several other packages. The total set of methods for a given generic function may change during a session, as additional packages are loaded. Each table must be consistent in the signature assumed for the generic function.
R distinguishes standard and nonstandard generic functions, with the former having a function body that does nothing but dispatch a method. For the most part, the distinction is just one of simplicity: knowing that a generic function only dispatches a method call allows some efficiencies and also removes some uncertainties.
In most cases, the generic function is the visible function corresponding to that name, in the corresponding package. There are two exceptions, implicit generic functions and the special computations required to deal with R's primitive functions. Packages can contain a table of implicit generic versions of functions in the package, if the package wishes to leave a function non-generic but to constrain what the function would be like if it were generic. Such implicit generic functions are created during the installation of the package, essentially by defining the generic function and possibly methods for it, and then reverting the function to its non-generic form. (See implicitGeneric for how this is done.) The mechanism is mainly used for functions in the older packages in R, which may prefer to ignore S4 methods. Even in this case, the actual mechanism is only needed if something special has to be specified. All functions have a corresponding implicit generic version defined automatically (an implicit, implicit generic function one might say). This function is a standard generic with the same arguments as the non-generic function, with the non-generic version as the default (and only) method, and with the generic signature being all the formal arguments except ....
The implicit generic mechanism is needed only to override some aspect
of the default definition.
One reason to do so would be to remove some arguments from the
signature.
Arguments that may need to be interpreted literally, or for which the
lazy evaluation mechanism of the language is needed, must not
be included in the signature of the generic function, since all
arguments in the signature will be evaluated in order to select a
method.
For example, the argument expr
to the function
with
is treated literally and must therefore be excluded
from the signature.
One would also need to define an implicit generic if the existing non-generic function were not suitable as the default method. Perhaps the function only applies to some classes of objects, and the package designer prefers to have no general default method. In the other direction, the package designer might have some ideas about suitable methods for some classes, if the function were generic. With reasonably modern packages, the simple approach in all these cases is just to define the function as a generic. The implicit generic mechanism is mainly attractive for older packages that do not want to require the methods package to be available.
Generic functions will also be defined but not obviously visible for
functions implemented as primitive functions in the base
package.
Primitive functions look like ordinary functions when printed but are
in fact not function objects but objects of two types interpreted by
the R evaluator to call underlying C code directly.
Since their entire justification is efficiency, R refuses to hide
primitives behind a generic function object.
Methods may be defined for most primitives, and corresponding metadata
objects will be created to store them.
Calls to the primitive still go directly to the C code, which will
sometimes check for applicable methods.
The definition of “sometimes” is that methods must have been
detected for the function in some package loaded in the session and
isS4(x)
is TRUE
for the first argument (or for the
second argument, in the case of binary operators).
You can test whether methods have been detected by calling
isGeneric
for the relevant function and you can examine
the generic function by calling getGeneric
, whether or
not methods have been detected.
For more on generic functions, see the references and also section 2
of the R Internals document supplied with R.
All method definitions are stored as objects from the
MethodDefinition
class.
Like the class of generic functions, this class extends ordinary R
functions with some additional slots: "generic"
, containing the
name and package of the generic function, and two signature slots,
"defined"
and "target"
, the first being the signature supplied when
the method was defined by a call to setMethod
.
The "target"
slot starts off equal to the "defined"
slot. When an inherited method is cached after being selected, as
described above, a copy is made with the appropriate "target"
signature.
Output from showMethods
, for example, includes both
signatures.
Method definitions are required to have the same formal arguments as the generic function, since the method dispatch mechanism does not rematch arguments, for reasons of both efficiency and consistency.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.5 for some details.)
For more specific information, see
setGeneric
, setMethod
, and
setClass
.
For the use of ... in methods, see dotsMethods.
In writing methods for an R package, it's common for these methods to
apply to a function (in another package) that is not generic in that
package; that is, there are no formal methods for the function in its
own package, although it may have S3 methods.
The programming in this case involves one extra step, to call
setGeneric()
to declare that the function is
generic in your package.
Calls to the function in your package will then use all methods defined there or in any other loaded package that creates the same generic function. Similarly, calls to the function in those packages will use your methods.
The original version, however, remains non-generic. Calls in that package or in other packages that use that version will not dispatch your methods except for special circumstances:
If the function is one of the primitive functions that accept methods, the internal C implementation will dispatch methods if one of the arguments is an S4 object, as should be the case.
If the other version of the function dispatches S3 methods and your methods are also registered as S3 methods, the method will usually be dispatched as that S3 method.
Otherwise, you will need to ensure that all calls to the function come from a package in which the function is generic, perhaps by copying code to your package.
Details and the underlying reasons are discussed in the following sections.
Creating methods for a function (any function) in a package means that calls to the function in that package will select methods according to the actual arguments. However, if the function was originally a non-generic in another package, calls to the function from that package will not dispatch methods. In addition, calls from any third package that imports the non-generic version will also not dispatch methods. This section considers the reason and how one might deal with the consequences.
The reason is simply the R namespace mechanism and its role in evaluating function calls. When a name (such as the name of a function) needs to be evaluated in a call to a function from some package, the evaluator looks first in the frame of the call, then in the namespace of the package and then in the imports to that package.
Defining methods for a function in a package ensures that calls to the function in that package will select the methods, because a generic version of the function is created in the namespace. Similarly, calls from another package that has or imports the generic version will select methods. Because the generic versions are identical, all methods will be available in all these packages.
However, calls from any package that imports the old version or just selects it from the search list will usually not select methods.
A an example, consider the function
data.frame()
in the base package.
This function takes any number of objects as arguments and attempts to combine
them as variables into a data frame object.
It does this by calling as.data.frame()
, also in the
base package, for each of the objects.
A reasonable goal would be to extend the classes of objects that can
be included in a data frame by defining methods for
as.data.frame()
.
But calls to data.frame()
,
will still use the version of that function in the base package, which
continues to call the non-generic as.data.frame()
in
that package.
The details of what happens and options for dealing with it depend on the form of the function: a primitive function; a function that dispatches S3 methods; or an ordinary R function.
Primitive functions are not actual R function objects. They go directly to internal C code. Some of them, however, have been implemented to recognize methods. These functions dispatch both S4 and S3 methods from the internal C code. There is no explicit generic function, either S3 or S4. The internal code looks for S4 methods if the first argument, or either of the arguments in the case of a binary operator, is an S4 object. If no S4 method is found, a search is made for an S3 method. So defining methods for these functions works as long as the relevant classes have been defined, which should always be the case.
A function dispatches S3 methods by calling
UseMethod()
, which does not look for
formal methods regardless of whether the first argument is an S4
object or not.
This applies to the as.data.frame()
example above.
To have methods called in this situation, your package must also define the
method as an S3 method, if possible. See section ‘S3
“Generic” Functions’.
In the third possibility, the function is defined with no expectation
of methods.
For example, the base package has a number of functions that compute
numerical decompositions of matrix arguments.
Some, such as chol()
and qr()
are implemented to dispatch S3 methods; others, such as
svd()
are implemented directly as a specific
computation.
A generic version of the latter functions can be written and called
directly to define formal methods, but no code in another package that
does not import this generic version will dispatch such methods.
In this case, you need to have the generic version used in all the indirect calls to the
function supplying arguments that should dispatch methods.
This may require supplying new functions that dispatch methods and
then call the function they replace.
For example, if S3 methods did not work for
as.data.frame()
, one could call a function that
applied the generic version to all its arguments and then called
data.frame()
as a replacement for that function.
If all else fails, it might be necessary to copy over the relevant
functions so that they would find the generic versions.
S3 method dispatch looks at the class of the first
argument.
S3 methods are ordinary functions with the same arguments as the
generic function.
The “signature” of an S3 method is identified by the name to
which the method is assigned, composed of the name of the
generic function, followed by "."
, followed by the name of the class.
For details, see UseMethod
.
To implement a method for one of these functions corresponding to S4
classes, there are two possibilities: either an S4 method or an S3 method with the
S4 class name.
The S3 method is only possible if the intended signature has the
first argument and nothing else.
In this case,
the recommended approach is to define the S3 method and also supply the
identical function as the definition of the S4 method.
If the S3 generic function was f3(x, ...)
and the S4 class for
the new method was
"myClass"
:
f3.myClass <- function(x, ...) { ..... }
setMethod("f3", "myClass", f3.myClass)
Defining both methods usually ensures that all calls to the original function will dispatch the intended method. The S4 method alone would not be called from other packages using the original version of the function. On the other hand, an S3 method alone will not be called if there is any eligible non-default S4 method.
S4 and S3 method selection are designed to follow compatible rules of
inheritance, as far as possible.
S3 classes can be used for any S4 method selection, provided that the
S3 classes have been registered by a call to
setOldClass
, with that call specifying the correct S3
inheritance pattern.
S4 classes can be used for any S3 method selection; when an S4 object
is detected, S3 method selection uses the contents of
extends(class(x))
as the equivalent of the S3
inheritance (the inheritance is cached after the first call).
An existing S3 method may not behave as desired for an S4 subclass, in
which case utilities such as asS3
and
S3Part
may be useful. If the S3 method fails on the S4
object, asS3(x)
may be passed instead; if the object returned
by the S3 method needs to be incorporated in the S4 object, the
replacement function for S3Part
may be useful.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Methods_for_S3 for suggested implementation of methods that work for both S3 and S4 dispatch.
## A class that extends a registered S3 class inherits that class' S3 ## methods. setClass("myFrame", contains = "data.frame", slots = c(timestamps = "POSIXt")) df1 <- data.frame(x = 1:10, y = rnorm(10), z = sample(letters,10)) mydf1 <- new("myFrame", df1, timestamps = Sys.time()) ## "myFrame" objects inherit "data.frame" S3 methods; e.g., for `[` mydf1[1:2, ] # a data frame object (with extra attributes) ## a method explicitly for "myFrame" class setMethod("[", signature(x = "myFrame"), function (x, i, j, ..., drop = TRUE) { S3Part(x) <- callNextMethod() x@timestamps <- c(Sys.time(), as.POSIXct(x@timestamps)) x } ) mydf1[1:2, ] setClass("myDateTime", contains = "POSIXt") now <- Sys.time() # class(now) is c("POSIXct", "POSIXt") nowLt <- as.POSIXlt(now)# class(nowLt) is c("POSIXlt", "POSIXt") mCt <- new("myDateTime", now) mLt <- new("myDateTime", nowLt) ## S3 methods for an S4 object will be selected using S4 inheritance ## Objects mCt and mLt have different S3Class() values, but this is ## not used. f3 <- function(x)UseMethod("f3") # an S3 generic to illustrate inheritance f3.POSIXct <- function(x) "The POSIXct result" f3.POSIXlt <- function(x) "The POSIXlt result" f3.POSIXt <- function(x) "The POSIXt result" stopifnot(identical(f3(mCt), f3.POSIXt(mCt))) stopifnot(identical(f3(mLt), f3.POSIXt(mLt))) ## An S4 object selects S3 methods according to its S4 "inheritance" setClass("classA", contains = "numeric", slots = c(realData = "numeric")) Math.classA <- function(x) { (getFunction(.Generic))(x@realData) } setMethod("Math", "classA", Math.classA) x <- new("classA", log(1:10), realData = 1:10) stopifnot(identical(abs(x), 1:10)) setClass("classB", contains = "classA") y <- new("classB", x) stopifnot(identical(abs(y), abs(x))) # (version 2.9.0 or earlier fails here) ## an S3 generic: just for demonstration purposes f3 <- function(x, ...) UseMethod("f3") f3.default <- function(x, ...) "Default f3" ## S3 method (only) for classA f3.classA <- function(x, ...) "Class classA for f3" ## S3 and S4 method for numeric f3.numeric <- function(x, ...) "Class numeric for f3" setMethod("f3", "numeric", f3.numeric) ## The S3 method for classA and the closest inherited S3 method for classB ## are not found. f3(x); f3(y) # both choose "numeric" method ## to obtain the natural inheritance, set identical S3 and S4 methods setMethod("f3", "classA", f3.classA) f3(x); f3(y) # now both choose "classA" method ## Need to define an S3 as well as S4 method to use on an S3 object ## or if called from a package without the S4 generic MathFun <- function(x) { # a smarter "data.frame" method for Math group for (i in seq_len(ncol(x))[sapply(x, is.numeric)]) x[, i] <- (getFunction(.Generic))(x[, i]) x } setMethod("Math", "data.frame", MathFun) ## S4 method works for an S4 class containing data.frame, ## but not for data.frame objects (not S4 objects) try(logIris <- log(iris)) #gets an error from the old method ## Define an S3 method with the same computation Math.data.frame <- MathFun logIris <- log(iris)
## A class that extends a registered S3 class inherits that class' S3 ## methods. setClass("myFrame", contains = "data.frame", slots = c(timestamps = "POSIXt")) df1 <- data.frame(x = 1:10, y = rnorm(10), z = sample(letters,10)) mydf1 <- new("myFrame", df1, timestamps = Sys.time()) ## "myFrame" objects inherit "data.frame" S3 methods; e.g., for `[` mydf1[1:2, ] # a data frame object (with extra attributes) ## a method explicitly for "myFrame" class setMethod("[", signature(x = "myFrame"), function (x, i, j, ..., drop = TRUE) { S3Part(x) <- callNextMethod() x@timestamps <- c(Sys.time(), as.POSIXct(x@timestamps)) x } ) mydf1[1:2, ] setClass("myDateTime", contains = "POSIXt") now <- Sys.time() # class(now) is c("POSIXct", "POSIXt") nowLt <- as.POSIXlt(now)# class(nowLt) is c("POSIXlt", "POSIXt") mCt <- new("myDateTime", now) mLt <- new("myDateTime", nowLt) ## S3 methods for an S4 object will be selected using S4 inheritance ## Objects mCt and mLt have different S3Class() values, but this is ## not used. f3 <- function(x)UseMethod("f3") # an S3 generic to illustrate inheritance f3.POSIXct <- function(x) "The POSIXct result" f3.POSIXlt <- function(x) "The POSIXlt result" f3.POSIXt <- function(x) "The POSIXt result" stopifnot(identical(f3(mCt), f3.POSIXt(mCt))) stopifnot(identical(f3(mLt), f3.POSIXt(mLt))) ## An S4 object selects S3 methods according to its S4 "inheritance" setClass("classA", contains = "numeric", slots = c(realData = "numeric")) Math.classA <- function(x) { (getFunction(.Generic))(x@realData) } setMethod("Math", "classA", Math.classA) x <- new("classA", log(1:10), realData = 1:10) stopifnot(identical(abs(x), 1:10)) setClass("classB", contains = "classA") y <- new("classB", x) stopifnot(identical(abs(y), abs(x))) # (version 2.9.0 or earlier fails here) ## an S3 generic: just for demonstration purposes f3 <- function(x, ...) UseMethod("f3") f3.default <- function(x, ...) "Default f3" ## S3 method (only) for classA f3.classA <- function(x, ...) "Class classA for f3" ## S3 and S4 method for numeric f3.numeric <- function(x, ...) "Class numeric for f3" setMethod("f3", "numeric", f3.numeric) ## The S3 method for classA and the closest inherited S3 method for classB ## are not found. f3(x); f3(y) # both choose "numeric" method ## to obtain the natural inheritance, set identical S3 and S4 methods setMethod("f3", "classA", f3.classA) f3(x); f3(y) # now both choose "classA" method ## Need to define an S3 as well as S4 method to use on an S3 object ## or if called from a package without the S4 generic MathFun <- function(x) { # a smarter "data.frame" method for Math group for (i in seq_len(ncol(x))[sapply(x, is.numeric)]) x[, i] <- (getFunction(.Generic))(x[, i]) x } setMethod("Math", "data.frame", MathFun) ## S4 method works for an S4 class containing data.frame, ## but not for data.frame objects (not S4 objects) try(logIris <- log(iris)) #gets an error from the old method ## Define an S3 method with the same computation Math.data.frame <- MathFun logIris <- log(iris)
The S3 and S4 software in R are two generations implementing functional object-oriented programming. S3 is the original, simpler for initial programming but less general, less formal and less open to validation. The S4 formal methods and classes provide these features but require more programming.
In modern R, the two versions attempt to work together. This documentation outlines how to write methods for both systems by defining an S4 method for a function that dispatches S3 methods.
The systems can also be combined by using an S3 class with S4 method
dispatch or in S4 class definitions. See setOldClass
.
The R evaluator will ‘dispatch’ a method from a function call
either when the body of the function calls the special primitive
UseMethod
or when the call is to one of the builtin
primitives such as the math
functions or the binary operators.
S3 method dispatch looks at the class of the first
argument or the class of either
argument in a call to one of the primitive binary operators.
In pure S3 situations, ‘class’ in this context means the class
attribute or the implied class for a basic data type such as
"numeric"
.
The first S3 method that matches a name in the class is called and the
value of that call is the value of the original function call.
For details, see S3Methods.
In modern R, a function meth
in a package is registered as an S3 method
for function fun
and class Class
by
including in the package's NAMESPACE
file the directive
S3method(fun, Class, meth)
By default (and traditionally), the third argument is taken to be the
function fun.Class
; that is,
the name of the
generic function, followed by "."
, followed by the name of the
class.
As with S4 methods, a method that has been registered will be added to a table of methods for this function when the corresponding package is loaded into the session. Older versions of R, copying the mechanism in S, looked for the method in the current search list, but packages should now always register S3 methods rather than requiring the package to be attached.
Two possible mechanisms for implementing a method corresponding to an S4 class, there are two possibilities are to register it as an S3 method with the S4 class name or to define and set an S4 method, which will have the side effect of creating an S4 generic version of this function.
For most situations either works, but the recommended approach is to do both: register the S3 method and supply the identical function as the definition of the S4 method. This ensures that the proposed method will be dispatched for any applicable call to the function.
As an example, suppose an S4 class "uncased"
is defined,
extending "character"
and intending to ignore upper- and
lower-case.
The base function unique
dispatches S3 methods.
To define the class and a method for this function:
setClass("uncased", contains = "character")
unique.uncased <- function(x, incomparables = FALSE, ...)
nextMethod(tolower(x))
setMethod("unique", "uncased", unique.uncased)
In addition, the NAMESPACE
for the package should contain:
S3method(unique, uncased)
exportMethods(unique)
The result is to define identical S3 and S4 methods and ensure that all
calls to unique
will dispatch that method when appropriate.
The reasons for defining both S3 and S4 methods are as follows:
An S4 method alone will not be seen if the S3 generic function
is called directly. This will be the case, for example, if some
function calls unique()
from a package that does not make
that function an S4 generic.
However, primitive functions and operators are exceptions: The internal C code will look for S4 methods if and only if the object is an S4 object. S4 method dispatch would be used to dispatch any binary operator calls where either of the operands was an S4 object, for example.
An S3 method alone will not be called if there is any eligible non-default S4 method.
So if a package defined an S3
method for unique
for an S4 class but another package
defined an S4 method for a superclass of that class, the
superclass method would be chosen, probably not what was
intended.
S4 and S3 method selection are designed to follow compatible rules of
inheritance, as far as possible.
S3 classes can be used for any S4 method selection, provided that the
S3 classes have been registered by a call to
setOldClass
, with that call specifying the correct S3
inheritance pattern.
S4 classes can be used for any S3 method selection; when an S4 object
is detected, S3 method selection uses the contents of
extends(class(x))
as the equivalent of the S3
inheritance (the inheritance is cached after the first call).
For the details of S4 and S3 dispatch see Methods_Details and S3Methods.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
"MethodsList"
, Defunct Representation of Methods This class of objects was used in the original implementation of the package to control method dispatch. Its use is now defunct, but object appear as the default method slot in generic functions. This and any other remaining uses will be removed in the future.
For the modern alternative, see listOfMethods.
The details in this documentation are retained to allow analysis of old-style objects.
Suppose a function f
has
formal arguments x
and y
. The methods list object for
that function has the object as.name("x")
as its
argument
slot. An element of the methods named "track"
is selected if the actual argument corresponding to x
is an
object of class "track"
. If there is such an element, it can
generally be either a function or another methods list object.
In the first case, the function defines the method to use for any call
in which x
is of class "track"
. In the second case, the
new methods list object defines the available methods depending on
the remaining formal arguments, in this example, y
.
Each method corresponds conceptually to a signature;
that is a named list of classes, with names corresponding to some or
all of the formal arguments. In the previous example, if selecting
class "track"
for x
, finding that the selection was
another methods list and then selecting class "numeric"
for
y
would produce a method associated with the signature
x = "track", y = "numeric"
.
argument
:Object of class "name"
. The name of the
argument being used for dispatch at this level.
methods
:A named list of the methods (and method lists) defined explicitly for this argument. The names are the names of classes, and the corresponding element defines the method or methods to be used if the corresponding argument has that class. See the details below.
allMethods
:A named list, contains
all the directly defined methods from the methods
slot, plus
any inherited methods. Ignored when methods tables are used for dispatch (see Methods_Details).
Class "OptionalMethods"
, directly.
"MethodWithNext"
Class of method definitions set up for callNextMethod
Objects from this class are generated as a side-effect of calls to
callNextMethod
.
.Data
:Object of class "function"
; the actual
function definition.
nextMethod
:Object of class "PossibleMethod"
the method to use in response to a callNextMethod()
call.
excluded
:Object of class "list"
; one or more
signatures excluded in finding the next method.
target
:Object of class "signature"
, from class
"MethodDefinition"
defined
:Object of class "signature"
, from
class "MethodDefinition"
generic
:Object of class "character"
; the function
for which the method was created.
Class "MethodDefinition"
, directly.
Class "function"
, from data part.
Class "PossibleMethod"
, by class "MethodDefinition"
.
Class "OptionalMethods"
, by class "MethodDefinition"
.
signature(method = "MethodWithNext")
:
used internally by method dispatch.
signature(method = "MethodWithNext")
: used
internally by method dispatch.
signature(object = "MethodWithNext")
callNextMethod
, and
class MethodDefinition
.
A call to new
returns a newly allocated object from the
class identified by the first argument. This call in turn calls the
method for the generic function initialize
corresponding to
the specified class, passing the ...
arguments to this
method.
In the default method for initialize()
, named arguments provide
values for the corresponding slots and unnamed arguments must be
objects from superclasses of this class.
A call to a generating function for a class (see
setClass
) will pass its ... arguments to a corresponding call to new()
.
new(Class, ...) initialize(.Object, ...)
new(Class, ...) initialize(.Object, ...)
Class |
either the name of a class, a |
... |
arguments to specify properties of the new object, to
be passed to |
.Object |
An object: see the “Initialize Methods” section. |
The generic function initialize
is not called directly.
A call to new
begins by copying the prototype object from
the class definition, and then calls intialize()
with this
object as the first argument, followed by the ... arguments.
The interpretation of the ...
arguments in a call to a
generator function or to new()
can be specialized to
particular classes, by defining an appropriate method for "initialize"
.
In the default method, unnamed arguments in the ...
are interpreted as
objects from a superclass, and named arguments are interpreted as
objects to be assigned into the correspondingly named slots.
Explicitly specified slots override inherited information for the same slot,
regardless of the order in which the arguments appear.
The initialize
methods do not have to have ...
as
their second argument (see the examples). Initialize methods are
often written when the natural parameters describing the new object
are not the names of the slots. If you do define such a method,
you should include ...
as a formal argument, and your method should pass such
arguments along via callNextMethod
.
This helps the definition of future subclasses of your class. If these
have additional slots and your method
does not have this argument, it will be difficult for these
slots to be included in an initializing call.
See
initialize-methods
for a discussion of some classes with existing
methods.
Methods for initialize
can be inherited only by simple
inheritance, since it is a requirement that the method return an
object from the target class. See the
simpleInheritanceOnly
argument to setGeneric
and
the discussion in setIs
for the general concept.
Note that the basic vector classes, "numeric"
, etc. are
implicitly defined, so one can use new
for these classes.
The ... arguments are interpreted as objects of this type and are
concatenated into the resulting vector.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Classes_Details for details of class definitions, and
setOldClass
for the relation to S3 classes.
## using the definition of class "track" from \link{setClass} ## a new object with two slots specified t1 <- new("track", x = seq_along(ydata), y = ydata) # a new object including an object from a superclass, plus a slot t2 <- new("trackCurve", t1, smooth = ysmooth) ### define a method for initialize, to ensure that new objects have ### equal-length x and y slots. In this version, the slots must still be ### supplied by name. setMethod("initialize", "track", function(.Object, ...) { .Object <- callNextMethod() if(length(.Object@x) != length(.Object@y)) stop("specified x and y of different lengths") .Object }) ### An alternative version that allows x and y to be supplied ### unnamed. A still more friendly version would make the default x ### a vector of the same length as y, and vice versa. setMethod("initialize", "track", function(.Object, x = numeric(0), y = numeric(0), ...) { .Object <- callNextMethod(.Object, ...) if(length(x) != length(y)) stop("specified x and y of different lengths") .Object@x <- x .Object@y <- y .Object })
## using the definition of class "track" from \link{setClass} ## a new object with two slots specified t1 <- new("track", x = seq_along(ydata), y = ydata) # a new object including an object from a superclass, plus a slot t2 <- new("trackCurve", t1, smooth = ysmooth) ### define a method for initialize, to ensure that new objects have ### equal-length x and y slots. In this version, the slots must still be ### supplied by name. setMethod("initialize", "track", function(.Object, ...) { .Object <- callNextMethod() if(length(.Object@x) != length(.Object@y)) stop("specified x and y of different lengths") .Object }) ### An alternative version that allows x and y to be supplied ### unnamed. A still more friendly version would make the default x ### a vector of the same length as y, and vice versa. setMethod("initialize", "track", function(.Object, x = numeric(0), y = numeric(0), ...) { .Object <- callNextMethod(.Object, ...) if(length(x) != length(y)) stop("specified x and y of different lengths") .Object@x <- x .Object@y <- y .Object })
S4 classes that are defined to extend one of the basic
vector classes should contain the class
structure
if they behave like structures; that
is, if they should retain their class behavior under math functions
or operators, so long as their length is unchanged.
On the other hand, if their class depends on the values in the
object, not just its structure, then they should lose that class
under any such transformations. In the latter case, they should be
defined to contain nonStructure
.
If neither of these strategies applies, the class likely needs some
methods of its own for Ops
, Math
, and/or
other generic functions. What is not usually a good idea is to allow
such computations to drop down to the default, base code. This is
inconsistent with most definitions of such classes.
Methods are defined for operators and math functions (groups
Ops
, Math
and Math2
). In
all cases the result is an ordinary vector of the appropriate type.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer.
setClass("NumericNotStructure", contains = c("numeric","nonStructure")) xx <- new("NumericNotStructure", 1:10) xx + 1 # vector log(xx) # vector sample(xx) # vector
setClass("NumericNotStructure", contains = c("numeric","nonStructure")) xx <- new("NumericNotStructure", 1:10) xx + 1 # vector log(xx) # vector sample(xx) # vector
This class of objects is used to represent ordinary character string
object names, extended with a package
slot naming the package
associated with each object.
The function getGenerics
returns an object of this class.
.Data
:Object of class "character"
: the
object names.
package
:Object of class "character"
the
package names.
Class "character"
, from data part.
Class "vector"
, by class "character"
.
Methods
for general background.
Assembles all relevant slot and method information for a class, with minimal markup for Rd processing; no QC facilities at present.
promptClass(clName, filename = NULL, type = "class", keywords = "classes", where = topenv(parent.frame()), generatorName = clName)
promptClass(clName, filename = NULL, type = "class", keywords = "classes", where = topenv(parent.frame()), generatorName = clName)
clName |
a character string naming the class to be documented. |
filename |
usually, a connection or a character string giving the
name of the file to which the documentation shell should be written.
The default corresponds to a file whose name is the topic name for
the class documentation, followed by |
type |
the documentation type to be declared in the output file. |
keywords |
the keywords to include in the shell of the
documentation. The keyword |
where |
where to look for the definition of the class and of methods that use it. |
generatorName |
the name for a generator function for this class; only required if a generator function was created and saved under a name different from the class name. |
The class definition is found on the search list. Using that definition, information about classes extended and slots is determined.
In addition, the currently available generics with methods for this
class are found (using getGenerics
). Note that these
methods need not be in the same environment as the class definition; in
particular, this part of the output may depend on which packages are
currently in the search list.
As with other prompt-style functions, unless filename
is
NA
, the documentation shell is written to a file, and a message
about this is given. The file will need editing to give information
about the meaning of the class. The output of
promptClass
can only contain information from the metadata
about the formal definition and how it is used.
If filename
is NA
, a list-style representation of the
documentation shell is created and returned. Writing the shell to a
file amounts to cat(unlist(x), file = filename, sep = "\n")
,
where x
is the list-style representation.
If a generator function is found assigned under the class name or
the optional generatorName
, skeleton documentation for that
function is added to the file.
If filename
is NA
, a list-style representation of the
documentation shell. Otherwise, the name of the file written to is
returned invisibly.
VJ Carey [email protected] and John Chambers
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
prompt
for documentation of functions,
promptMethods
for documentation of method definitions.
For processing of the edited documentation, either use
R CMD Rdconv
,
or include the edited file in the ‘man’ subdirectory of a
package.
## Not run: > promptClass("track") A shell of class documentation has been written to the file "track-class.Rd". ## End(Not run)
## Not run: > promptClass("track") A shell of class documentation has been written to the file "track-class.Rd". ## End(Not run)
Generates a shell of documentation for the methods of a generic function.
promptMethods(f, filename = NULL, methods)
promptMethods(f, filename = NULL, methods)
f |
a character string naming the generic function whose methods are to be documented. |
filename |
usually, a connection or a character string giving the
name of the file to which the documentation shell should be written.
The default corresponds to the coded topic name for these methods
(currently, |
methods |
optional If this argument is supplied, it is likely to be
|
If filename
is FALSE
, the text created is returned,
presumably to be inserted some other documentation file, such as the
documentation of the generic function itself (see
prompt
).
If filename
is NA
, a list-style representation of the
documentation shell is created and returned. Writing the shell to a
file amounts to cat(unlist(x), file = filename, sep = "\n")
,
where x
is the list-style representation.
Otherwise, the documentation shell is written to the file specified by
filename
.
If filename
is FALSE
, the text generated;
if filename
is NA
, a list-style representation of the
documentation shell.
Otherwise, the name of the file written to is returned invisibly.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
prompt
and
promptClass
The software described here allows packages to define reference classes that behave in the style of “OOP” languages such as Java and C++. This model for OOP differs from the functional model implemented by S4 (and S3) classes and methods, in which methods are defined for generic functions. Methods for reference classes are “encapsulated” in the class definition.
Computations with objects from reference classes invoke methods on them and
extract or set their fields, using the `$`
operator in R.
The field and method computations potentially modify the object.
All computations referring to the objects see the modifications, in contrast to
the usual functional programming model in R.
A call to
setRefClass
in the source code for a package defines the class and returns a generator object.
Subsequent calls to the $methods()
method of the generator will define methods for the class.
As with functional classes, if the class is exported from the package,
it will be available when the package is loaded.
Methods are R functions. In their usual implementation, they refer to fields and other methods of the class directly by name. See the section on “Writing Reference Methods”.
As with functional classes, reference classes can inherit from other
reference classes via a contains=
argument to
setRefClass
. Fields and methods will be inherited, except where the
new class overrides method definitions. See the section on “Inheritance”.
setRefClass(Class, fields = , contains = , methods =, where =, inheritPackage =, ...) getRefClass(Class, where =)
setRefClass(Class, fields = , contains = , methods =, where =, inheritPackage =, ...) getRefClass(Class, where =)
Class |
character string name for the class. In the call to |
fields |
either a character vector of field names or a named list of the fields. The resulting fields will be accessed with reference semantics (see the section on “Reference Objects”). If the argument is a list, each element of the list should usually be the character string name of a class, in which case the object in the field must be from that class or a subclass. An alternative, but not generally recommended, is to supply an accessor function; see the section on “Implementation” for accessor functions and the related internal mechanism. Note that fields are distinct from slots. Reference classes should not define class-specific slots. See the note on slots in the “Implementation” section. |
contains |
optional vector of superclasses for this class. If a superclass is also a reference class, the fields and class-based methods will be inherited. |
methods |
a named list of function definitions that can be invoked on objects
from this class. These can also be created by invoking the
|
where |
for For |
inheritPackage |
Should objects from the new class inherit the package environment of a
contained superclass? Default |
... |
other arguments to be passed to |
setRefClass()
returns a generator function suitable for
creating objects from the class, invisibly. A call to this function
takes any number of arguments,
which will be passed on to the initialize method. If no
initialize
method is defined for the class or one of its
superclasses, the default method expects named arguments with the
name of one of the fields and unnamed arguments, if any, that are
objects from one of the superclasses of this class (but only
superclasses that are themselves reference classes have any effect).
The generator function is similar to the S4 generator function
returned by setClass
. In addition to being a generator
function, however, it is also a reference class generator object,
with reference class methods for various utilities. See the section
on reference class generator objects below.
getRefClass()
also returns the generator function for the
class. Note that the package slot in the value is the correct package
from the class definition, regardless of the where
argument,
which is used only to
find the class if necessary.
Normal objects in R are passed as arguments in function calls consistently with functional programming semantics; that is, changes made to an object passed as an argument are local to the function call. The object that supplied the argument is unchanged.
The functional model (sometimes called pass-by-value, although this is inaccurate for R) is suitable for many statistical computations and is implicit, for example, in the basic R software for fitting statistical models. In some other situations, one would like all the code dealing with an object to see the exact same content, so that changes made in any computation would be reflected everywhere. This is often suitable if the object has some “objective” reality, such as a window in a user interface.
In addition, commonly used languages, including Java, C++ and many
others, support a version of classes and methods assuming reference
semantics.
The corresponding programming mechanism
is to invoke a method on an object.
In the R syntax we use "$"
for this operation; one invokes a method,
m1
say, on an object x
by the expression
x$m1(...)
.
Methods in this paradigm are associated with the object, or more precisely with the class of the object, as opposed to methods in a function-based class/method system, which are fundamentally associated with the function (in R, for example, a generic function in an R session has a table of all its currently known methods). In this document “methods for a class” as opposed to “methods for a function” will make the distinction.
Objects in this paradigm usually have named fields on which
the methods operate.
In the R implementation, the fields are defined when the class is
created.
The field itself can optionally have a specified class, meaning that only objects
from this class or one of its subclasses can be assigned to the field.
By default, fields have class "ANY"
.
Fields are accessed by reference. In particular, invoking a method may modify the content of the fields.
Programming for such classes involves writing new methods for a
particular class.
In the R implementation, these methods are R functions, with zero or
more formal arguments.
For standard reference methods, the object itself is not an explicit
argument to the method.
Instead, fields and methods for the class can be referred to by name
in the method definition.
The implementation uses R environments to make fields and other methods
available by name within the method.
Specifically, the parent environment of the method is the object itself.
See the section on “Writing
Reference Methods”.
This special use of environments is optional. If a method is defined
with an initial formal argument .self
, that will be passed in
as the whole object, and the method follows the standard rules for any
function in a package. See the section on “External Methods”
The goal of the software described here is to provide a uniform programming style in R for software dealing with reference classes, whether implemented directly in R or through an interface to one of the OOP languages.
Reference methods are functions supplied as elements of a named list,
either
when invoking $methods()
on a generator object g
or as
the argument methods
in a call to setRefClass
.
The two mechanisms have the same effect, but the first makes the code more readable.
Methods are written as ordinary R functions but have some special features and restrictions in their usual form. In contrast to some other languages (e.g., Python), the object itself does not need to be an argument in the method definition. The body of the function can contain calls to any other reference method, including those inherited from other reference classes and may refer to methods and to fields in the object by name.
Alternatively, a method may be an external method.
This is signalled by .self
being the first formal argument to the method.
The body of the method then works like any ordinary function.
The methods are called like other methods (without the .self
argument, which is supplied internally and always refers to the object
itself).
Inside the method, fields and other methods are accessed in the form
.self$x
.
External methods exist so that reference classes can inherit the
package environment of superclasses
in other packages; see the section on “External Methods”.
Fields may be modified in a method by using the
non-local assignment operator, <<-
, as in the $edit
and $undo
methods in the example below.
Note that non-local assignment is required: a local assignment with
the <-
operator just creates a local object in the function
call, as it would in any R function.
When methods are installed, a heuristic check is made for local
assignments to field names and a warning issued if any are detected.
Reference methods should be kept simple; if they need to do some specialized R computation, that computation should use a separate R function that is called from the reference method. Specifically, methods can not use special features of the enclosing environment mechanism, since the method's environment is used to access fields and other methods. In particular, methods should not use non-exported entries in the package's namespace, because the methods may be inherited by a reference class in another package.
Two method names are interpreted specially, initialize
and finalize
. If an initialize
method is defined, it
will be invoked when an object is generated from the class. See the
discussion of method $new(...)
in the section “Initialization Methods”.
If a finalize
method is defined, a function will be
registered to invoke it before the environment in
the object is discarded by the garbage collector; finalizers are
registered with atexit=TRUE
, and so are also run at the end of
R sessions. See the matrix viewer example for both initialize and
finalize methods.
Reference methods can not themselves be generic functions; if you want additional function-based method dispatch, write a separate generic function and call that from the method.
Two special object names are available.
The entire object can be referred to in a method by the reserved
name .self
.
The object .refClassDef
contains the definition of the
class of the object.
These are accessed as fields but are read-only, with one exception.
In principal, the .self
field can be modified in the $initialize
method, because the object is still being created at this stage.
This is not recommended, as it can invalidate the object with respect
to its class.
The methods available include methods inherited from superclasses, as discussed in the section “Inheritance”.
Only methods actually used will be included in the environment
corresponding to an individual object. To declare that a method requires a
particular other method, the first method should include a call
to $usingMethods()
with the name of the other method as an argument.
Declaring the methods this way is essential if the other method is used indirectly (e.g., via sapply()
or do.call()
).
If it is called directly, code analysis will find it.
Declaring the method is harmless in any case, however, and may aid
readability of the source code.
Documentation for the methods can be obtained by the $help
method for the generator object.
Methods for classes are not documented in the Rd
format used
for R functions.
Instead, the $help
method prints the calling sequence of the method, followed by
self-documentation from the method definition, in the style of Python.
If the first element of the body of the method is a literal character
string (possibly multi-line), that string is interpreted as documentation.
See the method definitions in the example.
If the class has a method defined for $initialize()
,
this method will be called once the reference object has been
created. You should write such a method for a class that needs to do
some special initialization.
In particular, a reference method is recommended rather than a method
for the S4 generic function initialize()
, because some special initialization is
required for reference objects before the initialization of
fields.
As with S4 classes, methods are written for $initialize()
and not for $new()
,
both for the previous reason and also because $new()
is invoked on the generator object and would be a method for that class.
The default method for $initialize()
is equivalent to invoking the method $initFields(...)
.
Named arguments assign initial values to the corresponding fields.
Unnamed arguments must be objects from this class or a reference
superclass of this class.
Fields will be initialized to the contents of the fields in such
objects, but named arguments override the corresponding inherited
fields.
Note that fields are simply assigned. If the field is itself a
reference object, that object is not copied.
The new and previous object will share the reference.
Also, a field assigned from an unnamed argument counts as an
assignment for locked fields.
To override an inherited value for a locked field, the new value must
be one of the named arguments in the initializing call.
A later assignment of the field will result in an error.
Initialization methods need some care in design.
The generator
for a reference class will be called with no arguments, for example
when copying the object.
To ensure that these calls do not fail, the method must have defaults
for all arguments or check for missing()
.
The method
should include ...
as an argument and
pass this on via $callSuper()
(or $initFields()
if
you know that your superclasses have no initialization methods).
This allows future class definitions that subclass this class, with
additional fields.
Reference classes inherit from other reference classes by using the
standard R inheritance; that is, by including the superclasses in the
contains=
argument when creating the new class.
The names of the reference superclasses are in slot
refSuperClasses
of the class definition.
Reference classes can inherit from ordinary S4 classes also, but this
is usually a bad idea if it mixes reference fields and non-reference slots.
See the comments in the section on “Implementation”.
Class fields are inherited. A class definition can override a field of the same name in a superclass only if the overriding class is a subclass of the class of the inherited field. This ensures that a valid object in the field remains valid for the superclass as well.
Inherited methods are installed in the same way as directly specified methods. The code in a method can refer to inherited methods in the same way as directly specified methods.
A method may override a method of the same name in a superclass.
The overriding method can call the superclass method by
callSuper(...)
as described below.
All reference classes inherit from the class "envRefClass"
.
All reference objects can use the following methods.
$callSuper(...)
Calls the method inherited from a reference superclass.
The call is meaningful only from within another method, and will be
resolved to call the inherited method of the same name.
The arguments to $callSuper
are passed to the superclass version.
See the matrix viewer class in the example.
Note that the intended arguments for the superclass method must be supplied explicitly; there is no convention for supplying the arguments automatically, in contrast to the similar mechanism for functional methods.
$copy(shallow = FALSE)
Creates a copy of the object. With reference classes, unlike ordinary
R objects, merely assigning the object with a different name does not
create an independent copy. If shallow
is FALSE
, any
field that is itself a reference object will also be copied, and
similarly recursively for its fields. Otherwise, while reassigning a
field to a new reference object will have no side effect, modifying
such a field will still be reflected in both copies of the object.
The argument has no effect on non-reference objects in fields. When
there are reference objects in some fields but it is asserted that
they will not be modified, using shallow = TRUE
will save some
memory and time.
$field(name, value)
With one argument, returns the field of the object with character
string name
. With two arguments, the corresponding field is
assigned value
. Assignment checks that name
specifies a
valid field, but the single-argument version will attempt to get
anything of that name from the object's environment.
The $field()
method replaces the direct use of a field name, when the name of the
field must be calculated, or for looping over several fields.
$export(Class)
Returns the result of coercing the object to Class
(typically
one of the superclasses of the object's class). Calling the method
has no side effect on the object itself.
$getRefClass()
; $getClass()
These return respectively the generator object and the formal class definition for the reference class of this object, efficiently.
$import(value, Class = class(value))
Import the object value
into the current object, replacing the
corresponding fields in the current object.
Object value
must come from one of the superclasses of the
current object's class.
If argument Class
is supplied, value
is first coerced to
that class.
$initFields(...)
Initialize the fields of the object from the supplied arguments. This
method is usually only called from a class with a $initialize()
method. It corresponds to the default initialization for reference
classes. If there are slots and non-reference superclasses, these may
be supplied in the ... argument as well.
Typically, a specialized $initialize()
method carries out its own computations, then invokes $initFields()
to perform standard initialization, as shown in the
matrixViewer
class in the example below.
$show()
This method is called when the object is printed automatically,
analogously to the show
function. A general method is
defined for class "envRefClass"
. User-defined reference
classes will often define their own method: see the Example below.
Note two points in the example. As with any show()
method, it
is a good idea to print the class explicitly to allow for subclasses
using the method. Second, to call the function show()
from the method, as opposed to the $show()
method itself, refer to methods::show()
explicitly.
$trace(what, ...)
, $untrace(what)
Apply the tracing and debugging facilities of the trace
function to the reference method what
.
All the arguments of the trace
function can be supplied, except for signature
, which is not
meaningful.
The reference method can be invoked on either an object or the generator for the class. See the section on Debugging below for details.
$usingMethods(...)
Reference methods used by this method are named as the arguments
either quoted or unquoted. In the code analysis phase of installing
the present method, the declared methods will be included. It is essential
to declare any methods used in a nonstandard way (e.g., via an apply function).
Methods called directly do not need to be declared, but it is harmless to do so.
$usingMethods()
does nothing at run time.
Objects also inherit two reserved fields:
.self
a reference to the entire object;
.refClassDef
the class definition.
The defined fields should not override these, and in general it is
unwise to define a field whose name begins with "."
, since the
implementation may use such names for special purposes.
The environment of a method in a reference class is the object itself,
as an environment.
This allows the method to refer directly to fields and other methods,
without using the whole object and the "$"
operator.
The parent of that environment is the namespace of the package in
which the reference class is defined.
Computations in the method have access to all the objects in the
package's namespace, exported or not.
When defining a class that contains a reference superclass in another
package, there is an ambiguity about which package namespace should
have that role.
The argument inheritPackage
to setRefClass()
controls
whether the environment of new objects should inherit from an
inherited class in another package or continue to inherit from the
current package's namespace.
If the superclass is “lean”, with few methods, or exists primarily to support a family of subclasses, then it may be better to continue to use the new package's environment. On the other hand, if the superclass was originally written as a standalone, this choice may invalidate existing superclass methods. For the superclass methods to continue to work, they must use only exported functions in their package and the new package must import these.
Either way, some methods may need to be written that do not assume the standard model for reference class methods, but behave essentially as ordinary functions would in dealing with reference class objects.
The mechanism is to recognize external methods.
An external method is
written as a function in which the first argument, named .self
,
stands for the reference class object.
This function is supplied as the definition for a reference class method.
The method will be called, automatically, with the first argument
being the current object and the other arguments, if any, passed along
from the actual call.
Since an external method is an ordinary function in the source code
for its package, it has access to all the objects in the namespace.
Fields and methods in the reference class must be referred to in the
form .self$name
.
If for some reason you do not want to use .self
as the first
argument, a function f()
can be converted explicitly as
externalRefMethod(f)
, which returns an object of class
"externalRefMethod"
that can be supplied as a method for the
class.
The first argument will still correspond to the whole object.
External methods can be supplied for any reference class, but there is no obvious advantage unless they are needed. They are more work to write, harder to read and (slightly) slower to execute.
NOTE: If you are the author of a package whose reference classes are likely to be subclassed in other packages, you can avoid these questions entirely by writing methods that only use exported functions from your package, so that all the methods will work from another package that imports yours.
The call to setRefClass
defines the specified class and
returns a “generator function” object for that class.
This object has class "refObjectGenerator"
; it inherits
from "function"
via "classGeneratorFunction"
and can be
called to generate new objects from the reference class.
The returned object is also a reference class object, although not of
the standard construction.
It can be used to invoke reference methods and access fields in the usual way, but
instead of being implemented directly as an environment it has a
subsidiary generator object as a slot, a
standard reference object (of class
"refGeneratorSlot"
).
Note that if one wanted to extend the reference class generator
capability with a subclass, this should be done by subclassing
"refGeneratorSlot"
, not "refObjectGenerator"
.
The fields are def
, the class definition, and className
,
the character string name of the class.
Methods generate objects
from the class, to access help on reference methods, and to
define new reference methods for the class.
The currently available methods are:
$new(...)
This method is equivalent to calling the generator function returned
by setRefClass
.
$help(topic)
Prints brief help on the topic. The topics recognized are reference method names, quoted or not.
The information printed is the calling sequence for the method, plus self-documentation if any. Reference methods can have an initial character string or vector as the first element in the body of the function defining the method. If so, this string is taken as self-documentation for the method (see the section on “Writing Reference Methods” for details).
If no topic is given or if the topic is not a method name, the definition of the class is printed.
$methods(...)
With no arguments, returns the names of the reference methods for this class. With one character string argument, returns the method of that name.
Named arguments
are method definitions, which will be
installed in the class, as if they had been supplied in the
methods
argument to setRefClass()
.
Supplying methods in this way, rather than in the call to
setRefClass()
, is recommended for the sake of clearer source
code.
See the section on “Writing Reference Methods” for details.
All methods for a class should be defined in the source code that defines the class, typically as part of a package. In particular, methods can not be redefined in a class in an attached package with a namespace: The class method checks for a locked binding of the class definition.
The new methods can refer to any currently defined method by name
(including other methods supplied in this call to
$methods()
).
Note though that previously defined methods are not re-analyzed
meaning that they will not call the new method (unless it redefines an
existing method of the same name).
To remove a method, supply NULL
as its new definition.
$fields()
Returns a list of the fields, each with its corresponding class.
Fields for which an accessor function was supplied in the definition
have class "activeBindingFunction"
.
$lock(...)
The fields named in the arguments are locked; specifically, after the lock method is called, the field may be set once. Any further attempt to set it will generate an error.
If called with no arguments, the method returns the names of the locked fields.
Fields that are defined by an explicit accessor function can not be locked (on the other hand, the accessor function can be defined to generate an error if called with an argument).
All code to lock fields should normally be part of the definition of a class; that is, the read-only nature of the fields is meant to be part of the class definition, not a dynamic property added later. In particular, fields can not be locked in a class in an attached package with a namespace: The class method checks for a locked binding of the class definition. Locked fields can not be subsequently unlocked.
$trace(what, ..., classMethod = FALSE)
Establish a traced version of method what
for objects generated
from this class. The generator object tracing works like the
$trace()
method for objects from the class, with two differences.
Since it changes the method definition in the class object itself,
tracing applies to all objects, not just the one on which the trace
method is invoked.
Second, the optional argument classMethod = TRUE
allows tracing
on the methods of the generator object itself.
By default, what
is interpreted as the name of a method in the
class for which this object is the generator.
$accessors(...)
A number of
systems using the OOP programming paradigm recommend or enforce
getter and setter methods
corresponding to each field, rather than direct access by name.
If you like this style and want to extract a field named abc
by x$getAbc()
and assign it by
x$setAbc(value)
,
the $accessors
method is a convenience function that creates such getter and setter methods for the
specified fields.
Otherwise there is no reason to use this mechanism. In particular, it
has nothing to do with the general ability to define fields by
functions as described in the section on “Reference Objects”.
Reference classes are implemented as S4 classes with a data part of
type "environment"
.
Fields correspond to named objects in the environment.
A field associated with a function is implemented as an
active binding.
In particular, fields with a specified class are implemented as a
special form of active binding to enforce valid assignment to the
field.
As a related feature, the element in the fields=
list supplied
to setRefClass
can be an accessor
function, a function of one argument that returns
the field if called with no argument or sets it to the value of the
argument otherwise.
Accessor functions are used internally and for inter-system interface
applications, but not generally recommended as they blur the concept
of fields as data within the object.
A field, say data
, can be accessed generally by an expression
of the form x$data
for any object from the relevant class.
In an internal method for this class, the field can be accessed by the name
data
.
A field that is not locked can be set by an expression of the form
x$data <- value
.
Inside an internal method, a field can be assigned by an expression of the form
x <<- value
.
Note the non-local assignment operator.
The standard R interpretation of this operator works to assign it in
the environment of the object.
If the field has an accessor function defined, getting and setting
will call that function.
When a method is invoked on an object, the function defining the method is installed in the object's environment, with the same environment as the environment of the function.
Reference classes can have validity methods in the same sense as any
S4 class (see setValidity
).
Such methods are often a good idea; they will be called by calling
validObject
and a validity method, if one is defined,
will be called when a reference object is created (from version 3.4 of
R on).
Just remember that these are S4 methods. The function will be called
with the object
as its argument. Fields and methods must be
accessed using $
.
Note: Slots. Because of the implementation, new reference classes can inherit from non-reference S4 classes as well as reference classes, and can include class-specific slots in the definition. This is usually a bad idea, if the slots from the non-reference class are thought of as alternatives to fields. Slots will as always be treated functionally. Therefore, changes to the slots and the fields will behave inconsistently, mixing the functional and reference paradigms for properties of the same object, conceptually unclear and prone to errors. In addition, the initialization method for the class will have to sort out fields from slots, with a good chance of creating anomalous behavior for subclasses of this class.
Inheriting from a class union, however, is a reasonable strategy (with all members of the union likely to be reference classes).
The standard R debugging and tracing facilities can be applied to
reference methods.
Reference methods can be passed to debug
and its
relatives from an object to debug further method invocations on that
object; for example, debug(xx$edit)
.
Somewhat more flexible use is available for a reference method version
of the trace
function.
A corresponding $trace()
reference method is available for
either an object or for the reference class generator
(xx$trace()
or mEdit$trace()
in the example below).
Using $trace()
on an object sets up a tracing
version for future invocations of the specified method for that
object.
Using $trace()
on the generator for the class sets up a
tracing version for all future objects from that class (and sometimes for
existing objects from the class if the method is not declared or
previously invoked).
In either case, all the arguments to the standard trace
function are available, except for signature=
which is
meaningless since reference methods can not be S4 generic functions.
This includes the typical style trace(what, browser)
for
interactive debugging and trace(what, edit = TRUE)
to edit the
reference method interactively.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 11.)
## a simple editor for matrix objects. Method $edit() changes some ## range of values; method $undo() undoes the last edit. mEdit <- setRefClass("mEdit", fields = list( data = "matrix", edits = "list")) ## The basic edit, undo methods mEdit$methods( edit = function(i, j, value) { ## the following string documents the edit method 'Replaces the range [i, j] of the object by value. ' backup <- list(i, j, data[i,j]) data[i,j] <<- value edits <<- c(edits, list(backup)) invisible(value) }, undo = function() { 'Undoes the last edit() operation and update the edits field accordingly. ' prev <- edits if(length(prev)) prev <- prev[[length(prev)]] else stop("No more edits to undo") edit(prev[[1]], prev[[2]], prev[[3]]) ## trim the edits list length(edits) <<- length(edits) - 2 invisible(prev) }) ## A method to automatically print objects mEdit$methods( show = function() { 'Method for automatically printing matrix editors' cat("Reference matrix editor object of class", classLabel(class(.self)), "\n") cat("Data: \n") methods::show(data) cat("Undo list is of length", length(edits), "\n") } ) xMat <- matrix(1:12,4,3) xx <- mEdit(data = xMat) xx$edit(2, 2, 0) xx xx$undo() mEdit$help("undo") stopifnot(all.equal(xx$data, xMat)) utils::str(xx) # show fields and names of methods ## A method to save the object mEdit$methods( save = function(file) { 'Save the current object on the file in R external object format. ' base::save(.self, file = file) } ) tf <- tempfile() xx$save(tf) ## Not run: ## Inheriting a reference class: a matrix viewer mv <- setRefClass("matrixViewer", fields = c("viewerDevice", "viewerFile"), contains = "mEdit", methods = list( view = function() { dd <- dev.cur(); dev.set(viewerDevice) devAskNewPage(FALSE) matplot(data, main = paste("After",length(edits),"edits")) dev.set(dd)}, edit = # invoke previous method, then replot function(i, j, value) { callSuper(i, j, value) view() })) ## initialize and finalize methods mv$methods( initialize = function(file = "./matrixView.pdf", ...) { viewerFile <<- file pdf(viewerFile) viewerDevice <<- dev.cur() dev.set(dev.prev()) callSuper(...) }, finalize = function() { dev.off(viewerDevice) }) ## debugging an object: call browser() in method $edit() xx$trace(edit, browser) ## debugging all objects from class mEdit in method $undo() mEdit$trace(undo, browser) ## End(Not run)
## a simple editor for matrix objects. Method $edit() changes some ## range of values; method $undo() undoes the last edit. mEdit <- setRefClass("mEdit", fields = list( data = "matrix", edits = "list")) ## The basic edit, undo methods mEdit$methods( edit = function(i, j, value) { ## the following string documents the edit method 'Replaces the range [i, j] of the object by value. ' backup <- list(i, j, data[i,j]) data[i,j] <<- value edits <<- c(edits, list(backup)) invisible(value) }, undo = function() { 'Undoes the last edit() operation and update the edits field accordingly. ' prev <- edits if(length(prev)) prev <- prev[[length(prev)]] else stop("No more edits to undo") edit(prev[[1]], prev[[2]], prev[[3]]) ## trim the edits list length(edits) <<- length(edits) - 2 invisible(prev) }) ## A method to automatically print objects mEdit$methods( show = function() { 'Method for automatically printing matrix editors' cat("Reference matrix editor object of class", classLabel(class(.self)), "\n") cat("Data: \n") methods::show(data) cat("Undo list is of length", length(edits), "\n") } ) xMat <- matrix(1:12,4,3) xx <- mEdit(data = xMat) xx$edit(2, 2, 0) xx xx$undo() mEdit$help("undo") stopifnot(all.equal(xx$data, xMat)) utils::str(xx) # show fields and names of methods ## A method to save the object mEdit$methods( save = function(file) { 'Save the current object on the file in R external object format. ' base::save(.self, file = file) } ) tf <- tempfile() xx$save(tf) ## Not run: ## Inheriting a reference class: a matrix viewer mv <- setRefClass("matrixViewer", fields = c("viewerDevice", "viewerFile"), contains = "mEdit", methods = list( view = function() { dd <- dev.cur(); dev.set(viewerDevice) devAskNewPage(FALSE) matplot(data, main = paste("After",length(edits),"edits")) dev.set(dd)}, edit = # invoke previous method, then replot function(i, j, value) { callSuper(i, j, value) view() })) ## initialize and finalize methods mv$methods( initialize = function(file = "./matrixView.pdf", ...) { viewerFile <<- file pdf(viewerFile) viewerDevice <<- dev.cur() dev.set(dev.prev()) callSuper(...) }, finalize = function() { dev.off(viewerDevice) }) ## debugging an object: call browser() in method $edit() xx$trace(edit, browser) ## debugging all objects from class mEdit in method $undo() mEdit$trace(undo, browser) ## End(Not run)
Remove the method for a given function and signature. Obsolete for ordinary applications: Method definitions in a package should never need to remove methods and it's very bad practice to remove methods that were defined in other packages.
removeMethod(f, signature, where)
removeMethod(f, signature, where)
f , signature , where
|
As for |
TRUE
if a method
was found to be removed.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
These are old utility functions to construct, respectively
a list designed to represent the slots and superclasses and
a list of prototype specifications. The representation()
function is no longer useful, since the arguments slots
and
contains
to setClass
are now recommended.
The prototype()
function may still be used for the
corresponding argument, but a
simple list of the same arguments works as well.
representation(...) prototype(...)
representation(...) prototype(...)
... |
The call to representation takes arguments that are single character strings. Unnamed arguments are classes that a newly defined class extends; named arguments name the explicit slots in the new class, and specify what class each slot should have. In the call to |
The representation
function applies tests for the validity of
the arguments. Each must specify the name of a class.
The classes named don't have to exist when representation
is
called, but if they do, then the function will check for any duplicate
slot names introduced by each of the inherited classes.
The arguments to prototype
are usually named initial values
for slots, plus an optional first argument that gives the object
itself. The unnamed argument is typically useful if there is a data
part to the definition (see the examples below).
The value of representation
is just the list of arguments, after these have been checked
for validity.
The value of prototype
is the object to be used as the
prototype. Slots will have been set consistently with the
arguments, but the construction does not use the class
definition to test validity of the contents (it hardly can, since
the prototype object is usually supplied to create the definition).
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
## representation for a new class with a directly define slot "smooth" ## which should be a "numeric" object, and extending class "track" representation("track", smooth ="numeric") ### >>> This *is* old syntax -- use 'contains=*, slots=*' instead <<< ### ========== ---------- ------ ====== setClass("Character",representation("character")) setClass("TypedCharacter",representation("Character",type="character"), prototype(character(0),type="plain")) ttt <- new("TypedCharacter", "foo", type = "character") setClass("num1", representation(comment = "character"), contains = "numeric", prototype = prototype(pi, comment = "Start with pi"))
## representation for a new class with a directly define slot "smooth" ## which should be a "numeric" object, and extending class "track" representation("track", smooth ="numeric") ### >>> This *is* old syntax -- use 'contains=*, slots=*' instead <<< ### ========== ---------- ------ ====== setClass("Character",representation("character")) setClass("TypedCharacter",representation("Character",type="character"), prototype(character(0),type="plain")) ttt <- new("TypedCharacter", "foo", type = "character") setClass("num1", representation(comment = "character"), contains = "numeric", prototype = prototype(pi, comment = "Start with pi"))
A regular (S4) class may contain an S3 class, if that class has been registered (by calling
setOldClass
). The functions described here provide
information about contained S3 classes. See the section ‘Functions’.
In modern R, these functions are not usually needed to program with objects from the S4 class. Standard computations work as expected, including method selection for both S4 and S3. To coerce an object to its contained S3 class, use either of the expressions:
as(object, S3Class); as(object, "S3")
where
S3Class
evaluates to the name of the contained class. These
return slightly different objects, which in rare cases may need to
be distinguished. See the section “Contained S3 Objects”.
S3Part(object, strictS3 = FALSE, S3Class) S3Class(object) isXS3Class(classDef) slotsFromS3(object) ## the replacement versions of the functions are not recommended ## Create a new object from the class or use the replacement version of as(). S3Part(object, strictS3 = FALSE, needClass = ) <- value S3Class(object) <- value
S3Part(object, strictS3 = FALSE, S3Class) S3Class(object) isXS3Class(classDef) slotsFromS3(object) ## the replacement versions of the functions are not recommended ## Create a new object from the class or use the replacement version of as(). S3Part(object, strictS3 = FALSE, needClass = ) <- value S3Class(object) <- value
object |
an object from some class that extends a registered S3 class, or a basic vector, matrix or array object type. For most of the functions, an S3 object can also be supplied, with the interpretation that it is its own S3 part. |
strictS3 |
If |
S3Class |
the |
classDef |
a class definition object, as returned by
The remaining arguments apply only to the replacement versions, which are not recommended. |
needClass |
Require that the replacement value be this class or a subclass of it. |
value |
For For |
S3Part
: Returns an object from the S3 class that appeared
in the contains=
argument to setClass
.
If called with strictS3 = TRUE
, S3Part()
constructs the underlying
S3 object by eliminating
all the formally defined slots and turning off the S4 bit of the
object. With strictS3 = FALSE
the object returned is from
the corresponding S4 class. For consistency and generality,
S3Part()
works also for classes that extend the basic vector,
matrix and array classes.
A call to is equivalent coercing the object to class "S3"
for
the strict case, or to whatever the specific S3 class was, for the
non-strict case. The as()
calls are usually easier for
readers to understand.
S3Class
: Returns the character vector of S3 class(es) stored in
the object, if the class has the corresponding .S3Class
slot.
Currently, the function defaults to class
otherwise.
isXS3Class
: Returns TRUE
or FALSE
according
to whether the class defined by ClassDef
extends S3 classes (specifically, whether it has the slot for
holding the S3 class).
slotsFromS3
: returns a list of the relevant slot classes, or an
empty list for any other object.
The function slotsFromS3()
is a generic function used
internally to access the slots associated with the S3 part of the
object. Methods for this function are created automatically when
setOldClass
is called with the S4Class
argument. Usually, there is only one S3 slot, containing the S3
class, but the S4Class
argument may provide additional slots,
in the case that the S3 class has some guaranteed attributes that
can be used as formal S4 slots. See the corresponding section in
the documentation of setOldClass
.
Registering an S3 class defines an S4 class. Objects from this
class are essentially identical in content to an object from the S3
class, except for two differences. The value returned by
class()
will always be a single string for the S4
object, and isS4()
will return TRUE
or
FALSE
in the two cases. See the example below. It is barely
possible that some S3 code will not work with the S4 object; if so,
use as(x, "S3")
.
Objects from a class that extends an S3 class will have some basic type and
possibly some attributes. For an S3 class that has an equivalent S4
definition (e.g., "data.frame"
), an extending S4 class will
have a data part and slots. For other S3 classes (e.g., "lm"
) an
object from the extending S4 class will be some sort of basic type,
nearly always a vector type (e.g., "list"
for "lm"
),
but the data part will not have a formal definition.
Registering an S3 class by a call to
setOldClass
creates a class of the same name with a slot ".S3Class"
to hold
the corresponding S3 vector of class strings.
New S4 classes that extend such
classes also have the same slot, set to the S3 class of the
contained S3 object,
which may be an
(S3) subclass of the registered class.
For example, an S4 class might contain the S3 class "lm"
, but
an object from the class might contain an object from class
"mlm"
, as in the "xlm"
example below.
R is somewhat arbitrary about what
it treats as an S3 class: "ts"
is, but "matrix"
and "array"
are not.
For classes that extend
those, assuming they contain an S3 class is incorrect and will cause some
confusion—not usually disastrous, but the better strategy
is to stick to the explicit “class”.
Thus as(x, "matrix")
rather than as(x, "S3")
or S3Part(x)
.
Objects in R have an internal bit that indicates whether or not to
treat the object as coming from an S4 class. This bit is tested by
isS4
and can be set on or off by asS4
.
The latter function, however, does no checking or interpretation;
you should only use it if you are very certain every detail has been
handled correctly.
As a friendlier alternative, methods have been defined for coercing
to the virtual classes "S3"
and "S4"
. The expressions
as(object, "S3")
and as(object, "S4")
return S3
and S4 objects, respectively. In addition, they attempt
to do conversions in a valid way, and also check validity when
coercing to S4.
The expression as(object, "S3")
can be used in two ways. For
objects from one of the registered S3 classes, the expression will
ensure that the class attribute is the full multi-string S3 class
implied by class(object)
. If the registered class has known
attribute/slots, these will also be provided.
Another use of as(object, "S3")
is to take an S4 object and
turn it into an S3 object with corresponding attributes. This is
only meaningful with S4 classes that have a data part. If you want
to operate on the object without invoking S4 methods, this
conversion is usually the safest way.
The expression as(object, "S4")
will use the attributes in
the object to create an object from the S4 definition of
class(object)
. This is a general mechanism to create
partially defined version of S4 objects via S3 computations (not
much different from invoking new
with corresponding
arguments, but usable in this form even if the S4 object has an
initialize method with different arguments).
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10, particularly Section 10.8)
## an "mlm" object, regressing two variables on two others sepal <- as.matrix(datasets::iris[,c("Sepal.Width", "Sepal.Length")]) fit <- lm(sepal ~ Petal.Length + Petal.Width + Species, data = datasets::iris) class(fit) # S3 class: "mlm", "lm" ## a class that contains "mlm" myReg <- setClass("myReg", slots = c(title = "character"), contains = "mlm") fit2 <- myReg(fit, title = "Sepal Regression for iris data") fit2 # shows the inherited "mlm" object and the title identical(S3Part(fit2), as(fit2, "mlm")) class(as(fit2, "mlm")) # the S4 class, "mlm" class(as(fit2, "S3")) # the S3 class, c("mlm", "lm") ## An object may contain an S3 class from a subclass of that declared: xlm <- setClass("xlm", slots = c(eps = "numeric"), contains = "lm") xfit <- xlm(fit, eps = .Machine$double.eps) [email protected] # c("mlm", lm")
## an "mlm" object, regressing two variables on two others sepal <- as.matrix(datasets::iris[,c("Sepal.Width", "Sepal.Length")]) fit <- lm(sepal ~ Petal.Length + Petal.Width + Species, data = datasets::iris) class(fit) # S3 class: "mlm", "lm" ## a class that contains "mlm" myReg <- setClass("myReg", slots = c(title = "character"), contains = "mlm") fit2 <- myReg(fit, title = "Sepal Regression for iris data") fit2 # shows the inherited "mlm" object and the title identical(S3Part(fit2), as(fit2, "mlm")) class(as(fit2, "mlm")) # the S4 class, "mlm" class(as(fit2, "S3")) # the S3 class, c("mlm", "lm") ## An object may contain an S3 class from a subclass of that declared: xlm <- setClass("xlm", slots = c(eps = "numeric"), contains = "lm") xfit <- xlm(fit, eps = .Machine$double.eps) xfit@.S3Class # c("mlm", lm")
Methods can be defined for group generic functions. Each group generic function has a number of member generic functions associated with it.
Methods defined for a group generic function cause the same method to be defined for each member of the group, but a method explicitly defined for a member of the group takes precedence over a method defined, with the same signature, for the group generic.
The functions shown in this documentation page all reside in the
methods package, but the mechanism is available to any
programmer, by calling setGroupGeneric
(provided package
methods is attached).
## S4 group generics: Arith(e1, e2) Compare(e1, e2) Ops(e1, e2) Logic(e1, e2) Math(x) Math2(x, digits) Summary(x, ..., na.rm = FALSE) Complex(z)
## S4 group generics: Arith(e1, e2) Compare(e1, e2) Ops(e1, e2) Logic(e1, e2) Math(x) Math2(x, digits) Summary(x, ..., na.rm = FALSE) Complex(z)
x , z , e1 , e2
|
objects. |
digits |
number of digits to be used in |
... |
further arguments passed to or from methods. |
na.rm |
logical: should missing values be removed? |
Methods can be defined for the group generic functions by calls to
setMethod
in the usual way.
Note that the group generic functions
should never be called directly
– a suitable error message will result if they are. When metadata
for a group generic is loaded, the methods defined become methods
for the members of the group, but only if no method has been
specified directly for the member function for the same signature.
The effect is that group generic definitions are selected before
inherited methods but after directly specified methods. For more on
method selection, see Methods_Details
.
There are also
S3 groups Math
, Ops
, Summary
and
Complex
, see ?S3groupGeneric
,
with no corresponding R objects, but these are irrelevant for S4
group generic functions.
The members of the group defined by a particular generic can be
obtained by calling getGroupMembers
. For the group
generic functions currently defined in this package the members are
as follows:
Arith
"+"
, "-"
, "*"
, "^"
,
"%%"
, "%/%"
, "/"
Compare
"=="
, ">"
, "<"
,
"!="
, "<="
, ">="
Logic
"&"
, "|"
.
Ops
"Arith"
, "Compare"
, "Logic"
Math
"abs"
, "sign"
, "sqrt"
,
"ceiling"
, "floor"
, "trunc"
,
"cummax"
, "cummin"
, "cumprod"
, "cumsum"
,
"log"
, "log10"
, "log2"
, "log1p"
,
"acos"
, "acosh"
,
"asin"
, "asinh"
, "atan"
, "atanh"
,
"exp"
, "expm1"
,
"cos"
, "cosh"
, "cospi"
,
"sin"
, "sinh"
, "sinpi"
,
"tan"
, "tanh"
, "tanpi"
,
"gamma"
, "lgamma"
, "digamma"
,
"trigamma"
Math2
"round"
, "signif"
Summary
"max"
, "min"
, "range"
,
"prod"
, "sum"
, "any"
, "all"
Complex
"Arg"
, "Conj"
, "Im"
,
"Mod"
, "Re"
Note that Ops
merely consists of three sub groups.
All the functions in these groups (other than the group generics themselves) are basic functions in R. They are not by default S4 generic functions, and many of them are defined as primitives. However, you can still define formal methods for them, both individually and via the group generics. It all works more or less as you might expect, admittedly via a bit of trickery in the background. See Methods_Details for details.
Note that two members of the Math
group, log
and
trunc
, have ... as an extra formal argument.
Since methods for Math
will have only one formal argument,
you must set a specific method for these functions in order to call
them with the extra argument(s).
For further details about group generic functions see section 10.5 of the second reference.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.5)
The function callGeneric
is nearly always
relevant when writing a method for a group generic. See the
examples below and in section 10.5 of Software for Data Analysis.
See S3groupGeneric for S3 group generics.
setClass("testComplex", slots = c(zz = "complex")) ## method for whole group "Complex" setMethod("Complex", "testComplex", function(z) c("groupMethod", callGeneric(z@zz))) ## exception for Arg() : setMethod("Arg", "testComplex", function(z) c("ArgMethod", Arg(z@zz))) z1 <- 1+2i z2 <- new("testComplex", zz = z1) stopifnot(identical(Mod(z2), c("groupMethod", Mod(z1)))) stopifnot(identical(Arg(z2), c("ArgMethod", Arg(z1))))
setClass("testComplex", slots = c(zz = "complex")) ## method for whole group "Complex" setMethod("Complex", "testComplex", function(z) c("groupMethod", callGeneric(z@zz))) ## exception for Arg() : setMethod("Arg", "testComplex", function(z) c("ArgMethod", Arg(z@zz))) z1 <- 1+2i z2 <- new("testComplex", zz = z1) stopifnot(identical(Mod(z2), c("groupMethod", Mod(z1)))) stopifnot(identical(Arg(z2), c("ArgMethod", Arg(z1))))
An object from this class represents a single ‘is’ relationship; lists of these objects are used to represent all the extensions (superclasses) and subclasses for a given class. The object contains information about how the relation is defined and methods to coerce, test, and replace correspondingly.
Objects from this class are generated by setIs
,
from direct calls and from the contains=
information in a call to setClass
, and from class unions created by setClassUnion
.
In the last case, the information is stored in defining the subclasses of the union class (allowing unions to contain sealed classes).
subClass
, superClass
:The classes being
extended: corresponding to the from
, and to
arguments to setIs
.
package
:The package to which that class belongs.
coerce
:A function to carry out the as() computation
implied by the relation. Note that these functions should
not be used directly. They only deal with the
strict=TRUE
calls to the as
function, with
the full method constructed from this mechanically.
test
:The function that would test whether the
relation holds. Except for explicitly specified test
arguments to setIs
, this function is trivial.
replace
:The method used to implement as(x,
Class) <- value
.
simple
:A "logical"
flag, TRUE
if this
is a simple relation, either because one class is contained in the
definition of another, or because a class has been explicitly
stated to extend a virtual class. For simple extensions, the
three methods are generated automatically.
by
:If this relation has been constructed transitively, the first intermediate class from the subclass.
dataPart
:A "logical"
flag, TRUE
if
the extended class is in fact the data part of the subclass. In
this case the extended class is a basic class (i.e., a type).
distance
:The distance between the two classes, 1 for directly contained classes, plus the number of generations between otherwise.
No methods defined with class "SClassExtension"
in the
signature.
is
,
as
, and the
classRepresentation
class.
Return superclasses of ClassDef
, possibly only non-virtual or
direct or simple ones.
These functions are designed to be fast, and consequently only work
with the contains
slot of the corresponding class definitions.
selectSuperClasses(Class, dropVirtual = FALSE, namesOnly = TRUE, directOnly = TRUE, simpleOnly = directOnly, where = topenv(parent.frame())) .selectSuperClasses(ext, dropVirtual = FALSE, namesOnly = TRUE, directOnly = TRUE, simpleOnly = directOnly)
selectSuperClasses(Class, dropVirtual = FALSE, namesOnly = TRUE, directOnly = TRUE, simpleOnly = directOnly, where = topenv(parent.frame())) .selectSuperClasses(ext, dropVirtual = FALSE, namesOnly = TRUE, directOnly = TRUE, simpleOnly = directOnly)
Class |
name of the class or (more efficiently) the class
definition object (see |
dropVirtual |
logical indicating if only non-virtual superclasses should be returned. |
namesOnly |
logical indicating if only a vector names instead of a named list class-extensions should be returned. |
directOnly |
logical indicating if only a direct super classes should be returned. |
simpleOnly |
logical indicating if only simple class extensions should be returned. |
where |
(only used when |
ext |
for |
a character
vector (if namesOnly
is true, as per
default) or a list of class extensions (as the contains
slot in
the result of getClass
).
The typical user level function is selectSuperClasses()
which calls .selectSuperClasses()
; i.e., the latter should only
be used for efficiency reasons by experienced useRs.
is
, getClass
; further, the more technical
class classRepresentation
documentation.
setClass("Root") setClass("Base", contains = "Root", slots = c(length = "integer")) setClass("A", contains = "Base", slots = c(x = "numeric")) setClass("B", contains = "Base", slots = c(y = "character")) setClass("C", contains = c("A", "B")) extends("C") #--> "C" "A" "B" "Base" "Root" selectSuperClasses("C") # "A" "B" selectSuperClasses("C", directOnly=FALSE) # "A" "B" "Base" "Root" selectSuperClasses("C", dropVirtual=TRUE, directOnly=FALSE)# ditto w/o "Root"
setClass("Root") setClass("Base", contains = "Root", slots = c(length = "integer")) setClass("A", contains = "Base", slots = c(x = "numeric")) setClass("B", contains = "Base", slots = c(y = "character")) setClass("C", contains = c("A", "B")) extends("C") #--> "C" "A" "B" "Base" "Root" selectSuperClasses("C") # "A" "B" selectSuperClasses("C", directOnly=FALSE) # "A" "B" "Base" "Root" selectSuperClasses("C", dropVirtual=TRUE, directOnly=FALSE)# ditto w/o "Root"
A call to setAs
defines a method for coercing an object of
class from
to class to
. The methods will then be used
by calls to as
for objects with class from
,
including calls that replace part of the object.
Methods for this purpose work indirectly, by defining methods for
function coerce
. The coerce
function is not to
be called directly, and method selection uses class inheritance only
on the first argument.
setAs(from, to, def, replace, where = topenv(parent.frame()))
setAs(from, to, def, replace, where = topenv(parent.frame()))
from , to
|
The classes between which the coerce methods
|
def |
function of one argument. It will get an object from
class |
replace |
if supplied, the function to use as a replacement
method, when The remaining argument will not be used in standard applications. |
where |
the position or environment in which to store the resulting methods. Do not use this argument when defining a method in a package. Only the default, the namespace of the package, should be used in normal situations. |
Objects from one class can turn into objects from another class
either automatically or by an explicit call to the as
function. Automatic conversion is special, and comes from the
designer of one class of objects asserting that this class extends
another class. The most common case is that one or more class names
are supplied in the contains=
argument to setClass
, in
which case the new class extends each of the earlier classes (in the
usual terminology, the earlier classes are superclasses of
the new class and it is a subclass of each of them).
This form of inheritance is called simple inheritance in R.
See setClass
for details.
Inheritance can also be defined explicitly by a call to
setIs
.
The two versions have slightly different implications for coerce methods.
Simple inheritance implies that inherited slots behave identically in the subclass and the superclass.
Whenever two classes are related by simple inheritance, corresponding coerce methods
are defined for both direct and replacement use of as
.
In the case of simple inheritance, these methods do the obvious
computation: they extract or replace the slots in the object that
correspond to those in the superclass definition.
The implicitly defined coerce methods may be overridden by a call
to setAs
; note, however, that the implicit methods are defined for each
subclass-superclass pair, so that you must override each of these
explicitly, not rely on inheritance.
When inheritance is defined by a call to setIs
, the coerce methods are provided explicitly, not generated automatically.
Inheritance will apply (to the from
argument, as described in the section below).
You could also supply methods via setAs
for non-inherited relationships, and now these also can be inherited.
For further on the distinction between simple and explicit inheritance, see setIs
.
as
and setAs
WorkThe function as
turns object
into an object
of class Class
. In doing so, it applies a “coerce
method”, using S4
classes and methods, but in a somewhat special way.
Coerce methods are methods for the function coerce
or, in the
replacement case the function `coerce<-`
.
These functions have two arguments in method signatures, from
and to
, corresponding to the class of the object and the
desired coerce class.
These functions must not be called directly, but are used to store
tables of methods for the use of as
, directly and for
replacements.
In this section we will describe the direct case, but except where
noted the replacement case works the same way, using `coerce<-`
and the replace
argument to setAs
, rather than
coerce
and the def
argument.
Assuming the object
is not already of the desired class,
as
first looks for a method in the table of methods
for the function
coerce
for the signature c(from = class(object), to =
Class)
, in the same way method selection would do its initial lookup.
To be precise, this means the table of both direct and inherited
methods, but inheritance is used specially in this case (see below).
If no method is found, as
looks for one.
First, if either Class
or class(object)
is a superclass
of the other, the class definition will contain the information needed
to construct a coerce method.
In the usual case that the subclass contains the superclass (i.e., has
all its slots), the method is constructed either by extracting or
replacing the inherited slots.
Non-simple extensions (the result of a call to setIs
)
will usually contain explicit methods, though possibly not for replacement.
If no subclass/superclass relationship provides a method, as
looks for an inherited method, but applying, inheritance for the argument from
only, not for
the argument to
(if you think about it, you'll probably agree
that you wouldn't want the result to be from some class other than the
Class
specified). Thus,
selectMethod("coerce", sig, useInherited= c(from=TRUE, to= FALSE))
replicates the method selection used by as()
.
In nearly all cases the method found in this way will be cached in the
table of coerce methods (the exception being subclass relationships with a test, which
are legal but discouraged).
So the detailed calculations should be done only on the first
occurrence of a coerce from class(object)
to Class
.
Note that coerce
is not a standard generic function. It is
not intended to be called directly. To prevent accidentally caching
an invalid inherited method, calls are routed to an equivalent call to
as
, and a warning is issued. Also, calls to
selectMethod
for this function may not represent the
method that as
will choose. You can only trust the result if
the corresponding call to as
has occurred previously in this
session.
With this explanation as background, the function setAs
does a
fairly obvious computation: It constructs and sets a method for the function
coerce
with signature c(from, to)
, using the def
argument to define the body of the method. The function supplied as
def
can have one argument (interpreted as an object to be
coerced) or two arguments (the from
object and the to
class). Either way, setAs
constructs a function of two
arguments, with the second defaulting to the name of the to
class. The method will be called from as
with the object
as the from
argument and no to
argument, with the default for this argument being the name of the intended
to
class, so the method can use this information in messages.
The direct version of the as
function also has a strict=
argument that defaults to TRUE
.
Calls during the evaluation of methods for other functions will set this argument to FALSE
.
The distinction is relevant when the object being coerced is from a simple subclass of the to
class; if strict=FALSE
in this case, nothing need be done.
For most user-written coerce methods, when the two classes have no subclass/superclass, the strict=
argument is irrelevant.
The replace
argument to setAs
provides a method for
`coerce<-`
.
As with all replacement methods, the last argument of the method must
have the name value
for the object on the right of the
assignment.
As with the coerce
method, the first two arguments are
from, to
; there is no strict=
option for the replace case.
The function coerce
exists as a repository for
such methods, to be selected as described above by the as
function. Actually dispatching the methods using
standardGeneric
could produce incorrect inherited methods, by using
inheritance on the
to
argument; as mentioned, this is not the logic used for
as
.
To prevent selecting and caching invalid methods, calls to
coerce
are
currently mapped into calls to as
, with a warning message.
Methods are pre-defined for coercing any object to one of the basic
datatypes. For example, as(x, "numeric")
uses the existing
as.numeric
function. These built-in methods can be listed by
showMethods("coerce")
.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
If you think of using try(as(x, cl))
, consider
canCoerce(x, cl)
instead.
## using the definition of class "track" from \link{setClass} setAs("track", "numeric", function(from) from@y) t1 <- new("track", x=1:20, y=(1:20)^2) as(t1, "numeric") ## The next example shows: ## 1. A virtual class to define setAs for several classes at once. ## 2. as() using inherited information setClass("ca", slots = c(a = "character", id = "numeric")) setClass("cb", slots = c(b = "character", id = "numeric")) setClass("id") setIs("ca", "id") setIs("cb", "id") setAs("id", "numeric", function(from) from@id) CA <- new("ca", a = "A", id = 1) CB <- new("cb", b = "B", id = 2) setAs("cb", "ca", function(from, to )new(to, a=from@b, id = from@id)) as(CB, "numeric")
## using the definition of class "track" from \link{setClass} setAs("track", "numeric", function(from) from@y) t1 <- new("track", x=1:20, y=(1:20)^2) as(t1, "numeric") ## The next example shows: ## 1. A virtual class to define setAs for several classes at once. ## 2. as() using inherited information setClass("ca", slots = c(a = "character", id = "numeric")) setClass("cb", slots = c(b = "character", id = "numeric")) setClass("id") setIs("ca", "id") setIs("cb", "id") setAs("id", "numeric", function(from) from@id) CA <- new("ca", a = "A", id = 1) CB <- new("cb", b = "B", id = 2) setAs("cb", "ca", function(from, to )new(to, a=from@b, id = from@id)) as(CB, "numeric")
Create a class definition and return a generator function to create objects from the class. Typical usage will be of the style:
myClass <- setClass("myClass", slots= ...., contains =....)
where the first argument is the name of the new class and, if supplied, the arguments
slots=
and contains=
specify the slots
in the new class and existing classes from which the new class
should inherit. Calls to setClass()
are normally found in the
source of a package; when the package is loaded the class will be
defined in the package's namespace. Assigning the generator
function with the name of the class is convenient for users, but
not a requirement.
setClass(Class, representation, prototype, contains=character(), validity, access, where, version, sealed, package, S3methods = FALSE, slots)
setClass(Class, representation, prototype, contains=character(), validity, access, where, version, sealed, package, S3methods = FALSE, slots)
Class |
character string name for the class. |
slots |
The names and classes for the slots in the new class. This argument
must be supplied by name, The argument must be vector with a names attribute, the names being those of the slots in
the new class. Each element of the vector specifies an
existing class; the corresponding slot must be from this class
or a subclass of it. Usually, this is a character vector
naming the classes. It's also legal for the elements of the
vector to be class representation objects, as returned by As a limiting
case, the argument may be an unnamed character
vector; the elements are taken as slot names and all slots have
the unrestricted class |
contains |
A vector specifying existing classes from which
this class should inherit. The new class will have all the slots
of the superclasses, with the same requirements on the classes
of these slots. This argument
must be supplied by name, See the section ‘Virtual Classes’ for the special
superclass |
prototype , where , validity , sealed , package
|
These arguments are currently allowed, but either they are unlikely to be useful or there are modern alternatives that are preferred.
|
representation , access , version , S3methods
|
All these arguments are deprecated from version 3.0.0 of R and should be avoided.
|
A generator function suitable for creating objects from the class is
returned, invisibly. A call to this function generates a call to
new
for the class. The call takes any number of arguments,
which will be passed on to the initialize method. If no
initialize
method is defined for the class or one of its
superclasses, the default method expects named arguments with the
name of one of the slots and unnamed arguments that are objects from
one of the contained classes.
Typically the generator function is assigned the name of the class,
for programming clarity. This is not a requirement and objects
from the class can also be generated directly from
new
. The advantages of the generator function are a
slightly simpler and clearer call, and that the call will contain
the package name of the class (eliminating any ambiguity if two
classes from different packages have the same name).
If the class is virtual, an attempt to generate an object from
either the generator or new()
will result in an error.
The two essential arguments other than the class name are
slots
and contains
, defining the explicit slots
and the inheritance (superclasses). Together, these arguments define
all the information in an object from this class; that is, the names
of all the slots and the classes required for each of them.
The name of the class determines which methods apply directly to objects from this class. The superclass information specifies which methods apply indirectly, through inheritance. See Methods_Details for inheritance in method selection.
The slots in a class definition will be the union of all the slots
specified directly by slots
and all the slots in all
the contained classes.
There can only be one slot with a given name.
A class may override the definition of a slot with a given name, but
only if the newly specified class is a subclass of the
inherited one.
For example, if the contained class had a slot a
with class
"ANY"
, then a subclass could specify a
with class
"numeric"
,
but if the original specification for the slot was class
"character"
, the new call to setClass
would generate an error.
Slot names "class"
and "Class"
are not allowed.
There are other slot names with a special meaning; these names start with
the "."
character. To be safe, you should define all of
your own slots with names starting with an alphabetic character.
Some inherited classes will be treated specially—object types, S3 classes and a few special cases—whether inherited directly or indirectly. See the next three sections.
Classes exist for which no actual objects can be created, the virtual classes.
The most common and useful form of virtual class is the class
union, a virtual class that is defined in a call to
setClassUnion()
rather than a call to
setClass()
.
This call lists the members of the union—subclasses
that extend the new class.
Methods that are written with the class union in the signature
are eligible for use with objects from any of the member classes.
Class
unions can include as members classes whose
definition is otherwise sealed, including basic R data types.
Calls to setClass()
will also create a virtual class,
either when only the Class
argument is supplied (no slots
or superclasses) or when the contains=
argument includes
the special class name "VIRTUAL"
.
In the latter case, a
virtual class may include
slots to provide some common behavior without fully defining
the object—see the class traceable
for an
example.
Note that "VIRTUAL"
does not carry over to subclasses; a
class that contains a virtual class is not itself automatically virtual.
In addition to containing other S4 classes, a class definition can
contain either an S3 class (see the next section) or a built-in R pseudo-class—one
of the R
object types or one of the special R pseudo-classes "matrix"
and
"array"
.
A class can contain at most one of the object types, directly or indirectly.
When it does, that contained class determines the “data part”
of the class.
This appears as a pseudo-slot, ".Data"
and can be treated as a
slot but actually determines
the type of objects from this slot.
Objects from the new class try to inherit the built in
behavior of the contained type.
In the case of normal R data types, including vectors, functions and
expressions, the implementation is relatively straightforward.
For any object x
from the class,
typeof(x)
will be the contained basic type; and a special
pseudo-slot, .Data
, will be shown with the corresponding class.
See the "numWithId"
example below.
Classes may also inherit from "vector"
, "matrix"
or
"array"
.
The data part of these objects can be any vector data type.
For an object from any class that does not contain one of these
types or classes,
typeof(x)
will be "S4"
.
Some R data types do not behave normally, in the sense that they are
non-local references or other objects that are not duplicated.
Examples include those corresponding to classes "environment"
, "externalptr"
, and "name"
.
These can not be the types for objects with user-defined
classes (either S4 or S3) because setting an attribute overwrites the
object in all contexts.
It is possible to define a class that inherits from such types,
through an indirect mechanism that stores the inherited object in a
reserved slot, ".xData"
.
See the
example for class "stampedEnv"
below.
An object from such a class does not have a ".Data"
pseudo-slot.
For most computations, these classes behave transparently as if they
inherited directly from the anomalous type.
S3 method dispatch and the relevant as.
type()
functions should behave correctly, but code that uses the type of the
object directly will not.
For example, as.environment(e1)
would work as expected with the
"stampedEnv"
class, but typeof(e1)
is "S4"
.
Old-style S3 classes have no formal definition. Objects are “from” the class when their class attribute contains the character string considered to be the class name.
Using such classes with formal classes and methods is necessarily a
risky business, since there are no guarantees about the content of the
objects or about consistency of inherited methods.
Given that, it is still possible to define a class that inherits from
an S3 class, providing that class has been registered as an old class
(see setOldClass
).
Broadly speaking, both S3 and S4 method dispatch try to behave
sensibly with respect to inheritance in either system.
Given an S4 object, S3 method dispatch and the inherits
function should use the S4 inheritance information.
Given an S3 object, an S4 generic function will dispatch S4 methods
using the S3 inheritance, provided that inheritance has been declared via
setOldClass
. For details, see setOldClass
and Section 10.8 of the reference.
Class definitions normally belong to packages (but can be defined in
the global environment as well, by evaluating the expression on the
command line or in a file sourced from the command line).
The corresponding package name is part of the class definition; that
is, part of the classRepresentation
object holding that
definition. Thus, two classes with the same name can exist in
different packages, for most purposes.
When a class name is supplied for a slot or a superclass in a call to
setClass
, a
corresponding class definition will be found, looking from the
namespace of the current package, assuming the call in question appears directly in the source for the
package, as it should to avoid ambiguity.
The class definition
must be already defined in this package, in the imports directives of
the package's DESCRIPTION
and
NAMESPACE
files or in the basic classes defined by the methods package.
(The ‘methods’ package must be included in the imports directives
for any package that uses
S4 methods and classes, to satisfy the
"CMD check"
utility.)
If a package imports two classes of the same name from separate packages, the packageSlot
of the name
argument needs to be set to the package name of the
particular class.
This should be a rare occurrence.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Classes_Details
for a general discussion of classes,
Methods_Details
for an analogous discussion of methods,
makeClassRepresentation
## A simple class with two slots track <- setClass("track", slots = c(x="numeric", y="numeric")) ## an object from the class t1 <- track(x = 1:10, y = 1:10 + rnorm(10)) ## A class extending the previous, adding one more slot trackCurve <- setClass("trackCurve", slots = c(smooth = "numeric"), contains = "track") ## an object containing a superclass object t1s <- trackCurve(t1, smooth = 1:10) ## A class similar to "trackCurve", but with different structure ## allowing matrices for the "y" and "smooth" slots setClass("trackMultiCurve", slots = c(x="numeric", y="matrix", smooth="matrix"), prototype = list(x=numeric(), y=matrix(0,0,0), smooth= matrix(0,0,0))) ## A class that extends the built-in data type "numeric" numWithId <- setClass("numWithId", slots = c(id = "character"), contains = "numeric") numWithId(1:3, id = "An Example") ## inherit from reference object of type "environment" stampedEnv <- setClass("stampedEnv", contains = "environment", slots = c(update = "POSIXct")) setMethod("[[<-", c("stampedEnv", "character", "missing"), function(x, i, j, ..., value) { ev <- as(x, "environment") ev[[i]] <- value #update the object in the environment x@update <- Sys.time() # and the update time x}) e1 <- stampedEnv(update = Sys.time()) e1[["noise"]] <- rnorm(10)
## A simple class with two slots track <- setClass("track", slots = c(x="numeric", y="numeric")) ## an object from the class t1 <- track(x = 1:10, y = 1:10 + rnorm(10)) ## A class extending the previous, adding one more slot trackCurve <- setClass("trackCurve", slots = c(smooth = "numeric"), contains = "track") ## an object containing a superclass object t1s <- trackCurve(t1, smooth = 1:10) ## A class similar to "trackCurve", but with different structure ## allowing matrices for the "y" and "smooth" slots setClass("trackMultiCurve", slots = c(x="numeric", y="matrix", smooth="matrix"), prototype = list(x=numeric(), y=matrix(0,0,0), smooth= matrix(0,0,0))) ## A class that extends the built-in data type "numeric" numWithId <- setClass("numWithId", slots = c(id = "character"), contains = "numeric") numWithId(1:3, id = "An Example") ## inherit from reference object of type "environment" stampedEnv <- setClass("stampedEnv", contains = "environment", slots = c(update = "POSIXct")) setMethod("[[<-", c("stampedEnv", "character", "missing"), function(x, i, j, ..., value) { ev <- as(x, "environment") ev[[i]] <- value #update the object in the environment x@update <- Sys.time() # and the update time x}) e1 <- stampedEnv(update = Sys.time()) e1[["noise"]] <- rnorm(10)
A class may be defined as the union of other classes; that is, as a virtual class defined as a superclass of several other classes. Class unions are useful in method signatures or as slots in other classes, when we want to allow one of several classes to be supplied.
setClassUnion(name, members, where) isClassUnion(Class)
setClassUnion(name, members, where) isClassUnion(Class)
name |
the name for the new union class. |
members |
the names of the classes that should be members of this union. |
where |
where to save the new class definition. In calls from a package's source code, should be omitted to save the definition in the package's namespace. |
Class |
the name or definition of a class. |
The classes in members
must be defined before creating the
union. However, members can be added later on to an existing
union, as shown in the example below. Class unions can be
members of other class unions.
Class unions are the only way to create a new superclass of
a class whose definition is sealed. The namespace of all
packages is sealed when the package is loaded, protecting the
class and other definitions from being overwritten from another
class or from the global environment. A call to
setIs
that tried to define a new superclass for
class "numeric"
, for example, would cause an error.
Class unions are the exception; the class union
"maybeNumber"
in the examples defines itself as a new
superclass of "numeric"
. Technically, it does not alter the
metadata object in the other package's namespace and, of course,
the effect of the class union depends on loading the package it
belongs to. But, basically, class unions are sufficiently useful
to justify the exemption.
The different behavior for class unions is made possible because the
class definition object for class unions has itself a special class,
"ClassUnionRepresentation"
, an extension of class
classRepresentation
.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
## a class for either numeric or logical data setClassUnion("maybeNumber", c("numeric", "logical")) ## use the union as the data part of another class setClass("withId", contains = "maybeNumber", slots = c(id = "character")) w1 <- new("withId", 1:10, id = "test 1") w2 <- new("withId", sqrt(w1)%%1 < .01, id = "Perfect squares") ## add class "complex" to the union "maybeNumber" setIs("complex", "maybeNumber") w3 <- new("withId", complex(real = 1:10, imaginary = sqrt(1:10))) ## a class union containing the existing class union "OptionalFunction" setClassUnion("maybeCode", c("expression", "language", "OptionalFunction")) is(quote(sqrt(1:10)), "maybeCode") ## TRUE
## a class for either numeric or logical data setClassUnion("maybeNumber", c("numeric", "logical")) ## use the union as the data part of another class setClass("withId", contains = "maybeNumber", slots = c(id = "character")) w1 <- new("withId", 1:10, id = "test 1") w2 <- new("withId", sqrt(w1)%%1 < .01, id = "Perfect squares") ## add class "complex" to the union "maybeNumber" setIs("complex", "maybeNumber") w3 <- new("withId", complex(real = 1:10, imaginary = sqrt(1:10))) ## a class union containing the existing class union "OptionalFunction" setClassUnion("maybeCode", c("expression", "language", "OptionalFunction")) is(quote(sqrt(1:10)), "maybeCode") ## TRUE
Create a generic version of the named function so that methods may
be defined for it. A call to setMethod
will call
setGeneric
automatically if applied to a non-generic
function.
An explicit call to setGeneric
is usually not required, but
doesn't hurt and makes explicit that methods are being defined for a
non-generic function.
Standard calls will be of the form:
setGeneric(name)
where name
specifies an existing function, possibly in another
package. An alternative when creating a new generic function in this package is:
setGeneric(name, def)
where the function definition def
specifies the formal
arguments and becomes the default method.
setGeneric(name, def= , group=list(), valueClass=character(), where= , package= , signature= , useAsDefault= , genericFunction= , simpleInheritanceOnly = )
setGeneric(name, def= , group=list(), valueClass=character(), where= , package= , signature= , useAsDefault= , genericFunction= , simpleInheritanceOnly = )
name |
The character string name of the generic function. |
def |
An optional function object, defining the non-generic
version, to become the default method. This is equivalent in
effect to assigning The following arguments are specialized, optionally used when creating a new generic function with non-standard features. They should not be used when the non-generic is in another package. |
group |
The name of the group generic function to which this function belongs. See Methods_Details for details of group generic functions in method selection and S4groupGeneric for existing groups. |
valueClass |
A character vector specifying one or more class names. The value returned by the generic function must have (or extend) this class, or one of the classes; otherwise, an error is generated. |
signature |
The vector of names from among the formal arguments to
the function, that will be allowed in the signature of methods for this
function, in calls to A non-standard signature for the generic function may be used to exclude arguments that take advantage of lazy evaluation; in particular, if the argument may not be evaluated then it cannot be part of the signature. While It's usually a mistake to omit arguments from the signature in the belief that this improves efficiency. For method selection, the arguments that are used in the signatures for the methods are what counts, and then only seriously on the first call to the function with that combination of classes. |
simpleInheritanceOnly |
Supply this argument as |
useAsDefault |
Override the usual default method mechanism. Only relevant when defining a nonstandard generic function. See the section ‘Specialized Local Generics’. The remaining arguments are obsolete for normal applications. |
package |
The name of the package with which this function is associated. Should be determined automatically from the non-generic version. |
where |
Where to store the resulting objects as side effects. The default, to store in the package's namespace, is the only safe choice. |
genericFunction |
Obsolete. |
The setGeneric
function exists for its side effect: saving the
generic function to allow methods to be specified later. It returns
name
.
The setGeneric
function is called to initialize a generic
function as preparation for defining some methods for that function.
The simplest and most common situation is that name
specifies
an existing function, usually in another package. You now want to
define methods for this function. In this case you should
supply only name
, for example:
setGeneric("colSums")
There must be an existing function of this name (in this case in
package "base"
). The non-generic function can be in the same
package as the call, typically the case when you are creating a new
function plus methods for it. When the function is in
another package, it must be available by name, for
example through an importFrom()
directive in this package's
NAMESPACE
file. Not required for functions in "base"
,
which are implicitly imported.
A generic version of
the function will be created in the current package. The existing function
becomes the default method, and the package slot of the new generic
function is set to the location of the original function
("base"
in the example).
Two special types of non-generic should be noted.
Functions that dispatch S3 methods by calling
UseMethod
are ordinary functions, not objects from the
"genericFunction"
class. They are made generic like any
other function, but some special considerations apply to ensure that
S4 and S3 method dispatch is consistent (see Methods_for_S3).
Primitive functions are handled in C code and don't exist as normal
functions.
A call to setGeneric
is allowed in the simple form, but no
actual generic function object is created. Method dispatch will
take place in the C code. See the section on Primitive Functions for
more details.
It's an important feature that the
identical generic function definition is created in every package that
uses the same setGeneric()
call.
When any of these packages is loaded into an R session, this
function will be added to a table of generic functions, and will
contain a methods table of all the available methods for the
function.
Calling setGeneric()
is not strictly
necessary before calling setMethod()
. If
the function specified in the call to setMethod
is not generic,
setMethod
will execute the call to setGeneric
itself.
In the case that the non-generic is in another package, does not
dispatch S3 methods and is not a primitive, a message is printed noting the
creation of the generic function the first time setMethod
is called.
The second common use of setGeneric()
is to create a new
generic function, unrelated to any existing function. See the
asRObject()
example below.
This case can be handled just like the previous examples, with only
the difference that the non-generic function exists in the
current package.
Again, the non-generic version becomes the default method.
For clarity it's best for the assignment to immediately precede the
call to setGeneric()
in the source code.
Exactly the same result can be obtained by supplying the default as
the def
argument instead of assigning it.
In some applications, there will be no completely general default
method. While there is a special mechanism for this (see the
‘Specialized Local Generics’ section), the recommendation is to provide a
default method that signals an error, but with a message that
explains as clearly as you can why a non-default method is needed.
The great majority of calls to setGeneric()
should either
have one argument to ensure that an existing function can have
methods, or arguments name
and def
to create a new
generic function and optionally a default method.
It is possible to create generic functions with nonstandard signatures, or functions that do additional computations besides method dispatch or that belong to a group of generic functions.
None of these mechanisms should be used with a non-generic function from a different package, because the result is to create a generic function that may not be consistent from one package to another. When any such options are used, the new generic function will be assigned with a package slot set to the current package, not the one in which the non-generic version of the function is found.
There is a mechanism to define a specialized generic version of a
non-generic function, the implicitGeneric
construction.
This defines the generic version, but then reverts the function to
it non-generic form, saving the implicit generic in a table to be
activated when methods are defined.
However, the mechanism can only legitimately be used either for a non-generic
in the same package or by the "methods"
package itself.
And in the first case, there is no compelling reason not to simply
make the function generic, with the non-generic as the default
method.
See implicitGeneric
for details.
The body of a generic function usually does nothing except for
dispatching methods by a call to standardGeneric
. Under some
circumstances you might just want to do some additional computation in
the generic function itself. As long as your function eventually
calls standardGeneric
that is permissible.
See the example "authorNames"
below.
In this case, the def
argument will define the nonstandard
generic, not the default method.
An existing non-generic of the same name and calling sequence should
be pre-assigned. It will become the default method, as usual.
(An alternative is the useAsDefault
argument.)
By default, the generic function can return any object. If
valueClass
is supplied, it should be a vector of class names;
the value returned by a method is then required to satisfy
is(object, Class)
for one of the specified classes. An empty
(i.e., zero length) vector of classes means anything is allowed. Note
that more complicated requirements on the result can be specified
explicitly, by defining a non-standard generic function.
If the def
argument calls standardGeneric()
(with or
without additional computations) and there is no existing
non-generic version of the function, the generic is created without
a default method. This is not usually a good idea: better to have a
default method that signals an error with a message explaining why
the default case is not defined.
A new generic function can be created belonging to an existing group
by including the group
argument. The argument list of the
new generic must agree with that of the group. See
setGroupGeneric
for defining a new group generic.
For the role of group generics in
dispatching methods, see GroupGenericFunctions and section
10.5 of the second reference.
A number of the basic R functions are specially implemented as
primitive functions, to be evaluated directly in the underlying C code
rather than by evaluating an R language definition. Most have
implicit generics (see implicitGeneric
), and become
generic as soon as methods (including group methods) are defined on
them. Others cannot be made generic.
Calling setGeneric()
for
the primitive functions in the base package differs in that it does not, in fact,
generate an explicit generic function.
Methods for primitives are selected and dispatched from
the internal C code, to satisfy concerns for efficiency.
The same is true for a few
non-primitive functions that dispatch internally. These include
unlist
and as.vector
.
Note, that the implementation restrict methods for primitive functions to signatures in which at least one of the classes in the signature is a formal S4 class. Otherwise the internal C code will not look for methods. This is a desirable restriction in principle, since optional packages should not be allowed to change the behavior of basic R computations on existing data types.
To see the generic version of a primitive function, use
getGeneric(name)
. The function
isGeneric
will tell you whether methods are defined
for the function in the current session.
Note that S4 methods can only be set on those primitives which are
‘internal generic’, plus %*%
.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.5 for some details.)
Methods_Details
and the links there for a general discussion,
dotsMethods
for methods that dispatch on
...
, and setMethod
for method definitions.
## Specify that this package will define methods for plot() setGeneric("plot") ## create a new generic function, with a default method setGeneric("props", function(object) attributes(object)) ### A non-standard generic function. It insists that the methods ### return a non-empty character vector (a stronger requirement than ### valueClass = "character" in the call to setGeneric) setGeneric("authorNames", function(text) { value <- standardGeneric("authorNames") if(!(is(value, "character") && any(nchar(value)>0))) stop("authorNames methods must return non-empty strings") value }) ## the asRObject generic function, from package XR ## Its default method just returns object ## See the reference, Chapter 12 for methods setGeneric("asRObject", function(object, evaluator) { object })
## Specify that this package will define methods for plot() setGeneric("plot") ## create a new generic function, with a default method setGeneric("props", function(object) attributes(object)) ### A non-standard generic function. It insists that the methods ### return a non-empty character vector (a stronger requirement than ### valueClass = "character" in the call to setGeneric) setGeneric("authorNames", function(text) { value <- standardGeneric("authorNames") if(!(is(value, "character") && any(nchar(value)>0))) stop("authorNames methods must return non-empty strings") value }) ## the asRObject generic function, from package XR ## Its default method just returns object ## See the reference, Chapter 12 for methods setGeneric("asRObject", function(object, evaluator) { object })
The setGroupGeneric
function behaves like setGeneric
except that it constructs a group generic function, differing in two
ways from an ordinary generic function. First, this function cannot
be called directly, and the body of the function created will contain
a stop call with this information. Second, the group generic function
contains information about the known members of the group, used to
keep the members up to date when the group definition changes, through
changes in the search list or direct specification of methods, etc.
All members of the group must have the identical argument list.
setGroupGeneric(name, def= , group=list(), valueClass=character(), knownMembers=list(), package= , where= )
setGroupGeneric(name, def= , group=list(), valueClass=character(), knownMembers=list(), package= , where= )
name |
the character string name of the generic function. |
def |
A function object. There isn't likely to be an existing nongeneric of this name, so some function needs to be supplied. Any known member or other function with the same argument list will do, because the group generic cannot be called directly. |
group , valueClass
|
arguments to pass to
|
knownMembers |
the names of functions that are known to be members of this group. This information is used to reset cached definitions of the member generics when information about the group generic is changed. |
package , where
|
passed to |
The setGroupGeneric
function exists for its side effect: saving the
generic function to allow methods to be specified later. It returns
name
.
Chambers, John M. (2016) Extending R Chapman & Hall
Methods_Details
and the links there for a general discussion,
dotsMethods
for methods that dispatch on
...
, and setMethod
for method definitions.
## Not run: ## the definition of the "Logic" group generic in the methods package setGroupGeneric("Logic", function(e1, e2) NULL, knownMembers = c("&", "|")) ## End(Not run)
## Not run: ## the definition of the "Logic" group generic in the methods package setGroupGeneric("Logic", function(e1, e2) NULL, knownMembers = c("&", "|")) ## End(Not run)
setIs
is an explicit alternative
to the contains=
argument to setClass
. It is
only needed to create relations with explicit test or coercion.
These have not proved to be of much practical value, so this
function should not likely be needed in applications.
Where the programming goal is to define methods for transforming one
class of objects to another, it is usually better practice to call
setAs()
, which requires the transformations to be done explicitly.
setIs(class1, class2, test=NULL, coerce=NULL, replace=NULL, by = character(), where = topenv(parent.frame()), classDef =, extensionObject = NULL, doComplete = TRUE)
setIs(class1, class2, test=NULL, coerce=NULL, replace=NULL, by = character(), where = topenv(parent.frame()), classDef =, extensionObject = NULL, doComplete = TRUE)
class1 , class2
|
the names of the classes between which |
coerce , replace
|
functions optionally supplied to coerce the object to
|
test |
a conditional relationship is defined by supplying this function. Conditional relations are discouraged and are not included in selecting methods. See the details section below. The remaining arguments are for internal use and/or usually omitted. |
extensionObject |
alternative to the |
doComplete |
when |
by |
In a call to |
where |
In a call to |
classDef |
Optional class definition for |
Arranging for a class to inherit from another class is a key tool in programming. In R, there are three basic techniques, the first two providing what is called “simple” inheritance, the preferred form:
By the contains=
argument in a call to setClass
. This
is and should be the most common mechanism. It arranges that the new
class contains all the structure of the existing class, and in
particular all the slots with the same class specified. The
resulting class extension is defined to be simple
, with
important implications for method definition (see the section on
this topic below).
Making class1
a subclass of a virtual class
either by a call to setClassUnion
to make the
subclass a member of a new class union, or by a call to
setIs
to add a class to an existing class union or as a new
subclass of an existing virtual class. In either case, the
implication should be that methods defined for the class union or
other superclass all work correctly for the subclass. This may
depend on some similarity in the structure of the subclasses or
simply indicate that the superclass methods are defined in terms
of generic functions that apply to all the subclasses. These
relationships are also generally simple.
Supplying coerce
and replace
arguments to setAs
.
R allows arbitrary inheritance relationships, using the same
mechanism for defining coerce methods by a call to
setAs
. The difference between the two is simply
that setAs
will require a call to as
for a conversion to take place, whereas after the call to
setIs
, objects will be automatically converted to
the superclass.
The automatic feature is the dangerous part, mainly because it results in the subclass potentially inheriting methods that do not work. See the section on inheritance below. If the two classes involved do not actually inherit a large collection of methods, as in the first example below, the danger may be relatively slight.
If the superclass inherits methods where the subclass has only a
default or remotely inherited method, problems are more likely.
In this case, a general
recommendation is to use the setAs
mechanism
instead, unless there is a strong counter reason. Otherwise, be prepared to
override some of the methods inherited.
With this caution given, the rest of this section describes what
happens when coerce=
and replace=
arguments are supplied
to setIs
.
The coerce
and replace
arguments are functions that
define how to coerce a class1
object to class2
, and
how to replace the part of the subclass object that corresponds to
class2
. The first of these is a function of one argument
which should be from
, and the second of two arguments
(from
, value
). For details, see the section on coerce
functions below .
When by
is specified, the coerce process first coerces to
this class and then to class2
. It's unlikely you
would use the by
argument directly, but it is used in defining
cached information about classes.
The value returned (invisibly) by
setIs
is the revised class definition of class1
.
The coerce
argument is a function that turns a
class1
object into a class2
object. The
replace
argument is a function of two arguments that modifies a class1
object (the first argument) to replace the part of it that
corresponds to class2
(supplied as value
, the second
argument). It then returns the modified object as the value of the
call. In other words, it acts as a replacement method to
implement the expression as(object, class2) <- value
.
The easiest way to think of the coerce
and replace
functions is by thinking of the case that class1
contains class2
in the usual sense, by including the slots of
the second class. (To repeat, in this situation you would not call
setIs
, but the analogy shows what happens when you do.)
The coerce
function in this case would just make a
class2
object by extracting the corresponding slots from the
class1
object. The replace
function would replace in
the class1
object the slots corresponding to class2
,
and return the modified object as its value.
For additional discussion of these functions, see
the documentation of the
setAs
function. (Unfortunately, argument
def
to that function corresponds to argument coerce
here.)
The inheritance relationship can also be conditional, if a function is supplied as the
test
argument. This should be a function of one argument
that returns TRUE
or FALSE
according to whether the
object supplied satisfies the relation is(object, class2)
.
Conditional relations between
classes are discouraged in general because they require a per-object
calculation to determine their validity. They cannot be applied
as efficiently as ordinary relations and tend to make the code that
uses them harder to interpret. NOTE: conditional inheritance
is not used to dispatch methods. Methods for conditional
superclasses will not be inherited. Instead, a method for the
subclass should be defined that tests the conditional relationship.
A method written for a particular signature (classes matched to one or more formal arguments to the function) naturally assumes that the objects corresponding to the arguments can be treated as coming from the corresponding classes. The objects will have all the slots and available methods for the classes.
The code that selects and dispatches the methods ensures that this
assumption is correct. If the inheritance was “simple”, that
is, defined by one or more uses of the contains=
argument in
a call to setClass
, no extra work is generally
needed. Classes are inherited from the superclass, with the same
definition.
When inheritance is defined by a general call to
setIs
, extra computations are required. This form of
inheritance implies that the subclass does not just contain
the slots of the superclass, but instead requires the explicit call
to the coerce and/or replace method. To ensure correct computation,
the inherited method is supplemented by calls to as
before the body of the method is evaluated.
The calls to as
generated in this case have the
argument strict = FALSE
, meaning that extra information can
be left in the converted object, so long as it has all the
appropriate slots. (It's this option that allows simple subclass
objects to be used without any change.) When you are writing your
coerce method, you may want to take advantage of that option.
Methods inherited through non-simple extensions can result in ambiguities
or unexpected selections. If class2
is a specialized class
with just a few applicable methods, creating the inheritance
relation may have little effect on the behavior of class1
.
But if class2
is a class with many methods, you may
find that you now inherit some undesirable methods for
class1
, in some cases, fail to inherit expected methods.
In the second example below, the non-simple inheritance from class
"factor"
might be assumed to inherit S3 methods via that
class. But the S3 class is ambiguous, and in fact is
"character"
rather than "factor"
.
For some generic functions, methods inherited by non-simple
extensions are either known to be invalid or sufficiently likely to
be so that the generic function has been defined to exclude such
inheritance. For example initialize
methods must
return an object of the target class; this is straightforward if the
extension is simple, because no change is made to the argument
object, but is essentially impossible. For this reason, the generic
function insists on only simple extensions for inheritance. See the
simpleInheritanceOnly
argument to setGeneric
for the mechanism. You can use this mechanism when defining new
generic functions.
If you get into problems with functions that do allow non-simple
inheritance, there are two basic choices. Either
back off from the setIs
call and settle for explicit coercing
defined by a call to setAs
; or, define explicit
methods involving class1
to override the bad inherited
methods. The first choice is the safer, when there are serious
problems.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
## Two examples of setIs() with coerce= and replace= arguments ## The first one works fairly well, because neither class has many ## inherited methods do be disturbed by the new inheritance ## The second example does NOT work well, because the new superclass, ## "factor", causes methods to be inherited that should not be. ## First example: ## a class definition (see \link{setClass} for class "track") setClass("trackCurve", contains = "track", slots = c( smooth = "numeric")) ## A class similar to "trackCurve", but with different structure ## allowing matrices for the "y" and "smooth" slots setClass("trackMultiCurve", slots = c(x="numeric", y="matrix", smooth="matrix"), prototype = structure(list(), x=numeric(), y=matrix(0,0,0), smooth= matrix(0,0,0))) ## Automatically convert an object from class "trackCurve" into ## "trackMultiCurve", by making the y, smooth slots into 1-column matrices setIs("trackCurve", "trackMultiCurve", coerce = function(obj) { new("trackMultiCurve", x = obj@x, y = as.matrix(obj@y), smooth = as.matrix(obj@smooth)) }, replace = function(obj, value) { obj@y <- as.matrix(value@y) obj@x <- value@x obj@smooth <- as.matrix(value@smooth) obj}) ## Second Example: ## A class that adds a slot to "character" setClass("stringsDated", contains = "character", slots = c(stamp="POSIXt")) ## Convert automatically to a factor by explicit coerce setIs("stringsDated", "factor", coerce = function(from) factor([email protected]), replace= function(from, value) { [email protected] <- as.character(value); from }) ll <- sample(letters, 10, replace = TRUE) ld <- new("stringsDated", ll, stamp = Sys.time()) levels(as(ld, "factor")) levels(ld) # will be NULL--see comment in section on inheritance above. ## In contrast, a class that simply extends "factor" ## has no such ambiguities setClass("factorDated", contains = "factor", slots = c(stamp="POSIXt")) fd <- new("factorDated", factor(ll), stamp = Sys.time()) identical(levels(fd), levels(as(fd, "factor")))
## Two examples of setIs() with coerce= and replace= arguments ## The first one works fairly well, because neither class has many ## inherited methods do be disturbed by the new inheritance ## The second example does NOT work well, because the new superclass, ## "factor", causes methods to be inherited that should not be. ## First example: ## a class definition (see \link{setClass} for class "track") setClass("trackCurve", contains = "track", slots = c( smooth = "numeric")) ## A class similar to "trackCurve", but with different structure ## allowing matrices for the "y" and "smooth" slots setClass("trackMultiCurve", slots = c(x="numeric", y="matrix", smooth="matrix"), prototype = structure(list(), x=numeric(), y=matrix(0,0,0), smooth= matrix(0,0,0))) ## Automatically convert an object from class "trackCurve" into ## "trackMultiCurve", by making the y, smooth slots into 1-column matrices setIs("trackCurve", "trackMultiCurve", coerce = function(obj) { new("trackMultiCurve", x = obj@x, y = as.matrix(obj@y), smooth = as.matrix(obj@smooth)) }, replace = function(obj, value) { obj@y <- as.matrix(value@y) obj@x <- value@x obj@smooth <- as.matrix(value@smooth) obj}) ## Second Example: ## A class that adds a slot to "character" setClass("stringsDated", contains = "character", slots = c(stamp="POSIXt")) ## Convert automatically to a factor by explicit coerce setIs("stringsDated", "factor", coerce = function(from) factor(from@.Data), replace= function(from, value) { from@.Data <- as.character(value); from }) ll <- sample(letters, 10, replace = TRUE) ld <- new("stringsDated", ll, stamp = Sys.time()) levels(as(ld, "factor")) levels(ld) # will be NULL--see comment in section on inheritance above. ## In contrast, a class that simply extends "factor" ## has no such ambiguities setClass("factorDated", contains = "factor", slots = c(stamp="POSIXt")) fd <- new("factorDated", factor(ll), stamp = Sys.time()) identical(levels(fd), levels(as(fd, "factor")))
These functions provide a mechanism for packages to specify computations to be done during the loading of a package namespace. Such actions are a flexible way to provide information only available at load time (such as locations in a dynamically linked library).
A call to setLoadAction()
or setLoadActions()
specifies
one or more functions to be called when the corresponding namespace is
loaded, with the ... argument names being used as identifying
names for the actions.
getLoadActions
reports the currently defined load actions,
given a package's namespace as its argument.
hasLoadAction
returns TRUE
if a load action
corresponding to the given name has previously been set for the
where
namespace.
evalOnLoad()
and evalqOnLoad()
schedule a specific
expression for evaluation at load time.
setLoadAction(action, aname=, where=) setLoadActions(..., .where=) getLoadActions(where=) hasLoadAction(aname, where=) evalOnLoad(expr, where=, aname=) evalqOnLoad(expr, where=, aname=)
setLoadAction(action, aname=, where=) setLoadActions(..., .where=) getLoadActions(where=) hasLoadAction(aname, where=) evalOnLoad(expr, where=, aname=) evalqOnLoad(expr, where=, aname=)
action , ...
|
functions of one or more arguments, to be called when this package is loaded. The functions will be called with one argument (the package namespace) so all following arguments must have default values. If the elements of ... are named, these names will be used for the corresponding load metadata. |
where , .where
|
the namespace of the package for which the list of load actions are defined. This argument is normally omitted if the call comes from the source code for the package itself, but will be needed if a package supplies load actions for another package. |
aname |
the name for the action. If an action is set without
supplying a name, the default uses the position in the sequence of
actions specified ( |
expr |
an expression to be evaluated in a load action in
environment |
The evalOnLoad()
and evalqOnLoad()
functions are for
convenience. They construct a function to evaluate the expression and
call setLoadAction()
to schedule a call to that function.
Each of the functions supplied as an argument to setLoadAction()
or setLoadActions()
is saved as metadata in the namespace,
typically that of the package containing the call to
setLoadActions()
. When this package's namespace is loaded, each
of these functions will be called. Action functions are called in the
order they are supplied to setLoadActions()
. The objects
assigned have metadata names constructed from the names supplied in the
call; unnamed arguments are taken to be named by their position in the
list of actions (".1"
, etc.).
Multiple calls to setLoadAction()
or setLoadActions()
can be used in a package's code; the actions will be scheduled after any
previously specified, except if the name given to setLoadAction()
is that of an existing action. In typical applications,
setLoadActions()
is more convenient when calling from the
package's own code to set several actions. Calls to
setLoadAction()
are more convenient if the action name is to be
constructed, which is more typical when one package constructs load
actions for another package.
Actions can be revised by assigning with the same name, actual or constructed, in a subsequent call. The replacement must still be a valid function, but can of course do nothing if the intention was to remove a previously specified action.
The functions must have at least one argument. They will be called with
one argument, the namespace of the package. The functions will be
called at the end of processing of S4 metadata, after dynamically
linking any compiled code, the call to .onLoad()
, if any, and
caching method and class definitions, but before the namespace is
sealed. (Load actions are only called if methods dispatch is on.)
Functions may therefore assign or modify objects in the namespace supplied as the argument in the call. The mechanism allows packages to save information not available until load time, such as values obtained from a dynamically linked library.
Load actions should be contrasted with user load hooks supplied by
setHook()
. User hooks are generally provided from
outside the package and are run after the namespace has been sealed.
Load actions are normally part of the package code, and the list of
actions is normally established when the package is installed.
Load actions can be supplied directly in the source code for a package. It is also possible and useful to provide facilities in one package to create load actions in another package. The software needs to be careful to assign the action functions in the correct environment, namely the namespace of the target package.
setLoadAction()
and setLoadActions()
are called for
their side effect and return no useful value.
getLoadActions()
returns a named list of the actions in the
supplied namespace.
hasLoadAction()
returns TRUE
if the specified action
name appears in the actions for this package.
setHook
for safer (since they are run after the
namespace is sealed) and more comprehensive versions in the
base package.
## Not run: ## in the code for some package ## ... somewhere else setLoadActions(function(ns) cat("Loaded package", sQuote(getNamespaceName(ns)), "at", format(Sys.time()), "\n"), setCount = function(ns) assign("myCount", 1, envir = ns), function(ns) assign("myPointer", getMyExternalPointer(), envir = ns)) ... somewhere later if(countShouldBe0) setLoadAction(function(ns) assign("myCount", 0, envir = ns), "setCount") ## End(Not run)
## Not run: ## in the code for some package ## ... somewhere else setLoadActions(function(ns) cat("Loaded package", sQuote(getNamespaceName(ns)), "at", format(Sys.time()), "\n"), setCount = function(ns) assign("myCount", 1, envir = ns), function(ns) assign("myPointer", getMyExternalPointer(), envir = ns)) ... somewhere later if(countShouldBe0) setLoadAction(function(ns) assign("myCount", 0, envir = ns), "setCount") ## End(Not run)
Create a method for a generic function, corresponding to a signature of classes for the arguments. Standard usage will be of the form:
setMethod(f, signature, definition)
where f
is the name of the function, signature
specifies the argument classes for which the method applies and definition
is the function definition for the method.
setMethod(f, signature=character(), definition, where = topenv(parent.frame()), valueClass = NULL, sealed = FALSE)
setMethod(f, signature=character(), definition, where = topenv(parent.frame()), valueClass = NULL, sealed = FALSE)
f |
The character-string name of the generic function. The unquoted name usually works as well (evaluating to the generic function), except for a few functions in the base package. |
signature |
The classes required for some of the arguments. Most applications just require one or two character strings matching the first argument(s) in the signature. More complicated cases follow R's rule for argument matching. See the details below; however, if the signature is not trivial, you should use |
definition |
A function definition, which will become the method
called when the arguments in a call to |
where , valueClass , sealed
|
These arguments are allowed but either obsolete or rarely appropriate.
|
The function exists for its side-effect. The definition will be stored in a special metadata object and incorporated in the generic function when the corresponding package is loaded into an R session.
When defining methods, it's important to ensure that methods are selected correctly; in particular, packages should be designed to avoid ambiguous method selection.
To describe method selection, consider first the case where only one
formal argument is in the active signature; that is, there is only one
argument, x
say, for which methods have been defined.
The generic function has a table of methods, indexed by the class for
the argument in the calls to setMethod
.
If there is a method in the table for the class of x
in the
call, this method is selected.
If not, the next best methods would correspond to the direct
superclasses of class(x)
—those appearing in the
contains=
argument when that class was defined.
If there is no method for any of these, the next best would correspond
to the direct superclasses of the first set of superclasses, and so
on.
The first possible source of ambiguity arises if the class has several
direct superclasses and methods have been defined for more than one of
those;
R will consider these equally valid and report an ambiguous choice.
If your package has the class definition for class(x)
, then you
need to define a method explicitly for this combination of generic
function and class.
When more than one formal argument appears in the method signature, R requires the “best” method to be chosen unambiguously for each argument. Ambiguities arise when one method is specific about one argument while another is specific about a different argument. A call that satisfies both requirements is then ambiguous: The two methods look equally valid, which should be chosen? In such cases the package needs to add a third method requiring both arguments to match.
The most common examples arise with binary operators. Methods may be
defined for individual operators, for special groups of operators such as
Arith
or for group Ops
.
If a package defines methods for generic functions, those methods
should be exported if any of the classes involved are exported; in
other words, if someone using the package might expect these methods
to be called.
Methods are exported by including an exportMethods()
directive
in the NAMESPACE
file for the package, with the arguments to
the directive being the names of the generic functions for which
methods have been defined.
Exporting methods is always desirable in the sense of declaring what
you want to happen, in that you do expect users to find such methods.
It can be essential in the case that the method was defined for a
function that is not originally a generic function in its own package
(for example, plot()
in the graphics
package). In this
case it may be that the version of the function in the R session is
not generic, and your methods will not be called.
Exporting methods for a function also exports the generic version of the function. Keep in mind that this does not conflict with the function as it was originally defined in another package; on the contrary, it's designed to ensure that the function in the R session dispatches methods correctly for your classes and continues to behave as expected when no specific methods apply. See Methods_Details for the actual mechanism.
The call to setMethod
stores the supplied method definition in
the metadata table for this generic function in the environment,
typically the global environment or the namespace of a package.
In the case of a package, the table object becomes part of the namespace or environment of the
package.
When the package is loaded into a later session, the
methods will be merged into the table of methods in the corresponding
generic function object.
Generic functions are referenced by the combination of the function name and
the package name;
for example, the function "show"
from the package
"methods"
.
Metadata for methods is identified by the two strings; in particular, the
generic function object itself has slots containing its name and its
package name.
The package name of a generic is set according to the package
from which it originally comes; in particular, and frequently, the
package where a non-generic version of the function originated.
For example, generic functions for all the functions in package base will
have "base"
as the package name, although none of them is an
S4 generic on that package.
These include most of the base functions that are primitives, rather than
true functions; see the section on primitive functions in the
documentation for setGeneric
for details.
Multiple packages can have methods for the same generic function; that is, for the same combination of generic function name and package name. Even though the methods are stored in separate tables in separate environments, loading the corresponding packages adds the methods to the table in the generic function itself, for the duration of the session.
The class
names in the signature can be any formal class, including basic
classes such as "numeric"
, "character"
, and
"matrix"
. Two additional special class names can appear:
"ANY"
, meaning that this argument can have any class at all;
and "missing"
, meaning that this argument must not
appear in the call in order to match this signature. Don't confuse
these two: if an argument isn't mentioned in a signature, it
corresponds implicitly to class "ANY"
, not to
"missing"
. See the example below. Old-style (‘S3’)
classes can also be used, if you need compatibility with these, but
you should definitely declare these classes by calling
setOldClass
if you want S3-style inheritance to work.
Method definitions can
have default expressions for arguments, but only if
the generic function must have some default expression for the
same argument. (This restriction is imposed by the way R manages
formal arguments.)
If so, and if the corresponding argument is
missing in the call to the generic function, the default expression
in the method is used. If the method definition has no default for
the argument, then the expression supplied in the definition of the
generic function itself is used, but note that this expression will
be evaluated using the enclosing environment of the method, not of
the generic function.
Method selection does
not evaluate default expressions.
All actual (non-missing) arguments in the signature of the
generic function will be evaluated when a method is selected—when
the call to standardGeneric(f)
occurs.
Note that specifying class "missing"
in the signature
does not require any default expressions.
It is possible to have some differences between the
formal arguments to a method supplied to setMethod
and those
of the generic. Roughly, if the generic has ... as one of its
arguments, then the method may have extra formal arguments, which
will be matched from the arguments matching ... in the call to
f
. (What actually happens is that a local function is
created inside the method, with the modified formal arguments, and the method
is re-defined to call that local function.)
Method dispatch tries to match the class of the actual arguments in a
call to the available methods collected for f
. If there is a
method defined for the exact same classes as in this call, that
method is used. Otherwise, all possible signatures are considered
corresponding to the actual classes or to superclasses of the actual
classes (including "ANY"
).
The method having the least distance from the actual classes is
chosen; if more than one method has minimal distance, one is chosen
(the lexicographically first in terms of superclasses) but a warning
is issued.
All inherited methods chosen are stored in another table, so that
the inheritance calculations only need to be done once per session
per sequence of actual classes.
See
Methods_Details and Section 10.7 of the reference for more details.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
Methods_for_Nongenerics discusses method definition for functions that are not generic functions in their original package; Methods_for_S3 discusses the integration of formal methods with the older S3 methods.
method.skeleton
, which is the recommended way to generate a skeleton of the call to setMethod
, with the correct formal arguments and other details.
Methods_Details and the links there for a general discussion, dotsMethods
for methods that dispatch on
“...”, and setGeneric
for generic functions.
## examples for a simple class with two numeric slots. ## (Run example(setMethod) to see the class and function definitions) ## methods for plotting track objects ## ## First, with only one object as argument, plot the two slots ## y must be included in the signature, it would default to "ANY" setMethod("plot", signature(x="track", y="missing"), function(x, y, ...) plot(x@x, x@y, ...) ) ## plot numeric data on either axis against a track object ## (reducing the track object to the cumulative distance along the track) ## Using a short form for the signature, which matches like formal arguments setMethod("plot", c("track", "numeric"), function(x, y, ...) plot(cumdist(x@x, x@y), y, xlab = "Distance",...) ) ## and similarly for the other axis setMethod("plot", c("numeric", "track"), function(x, y, ...) plot(x, cumdist(y@x, y@y), ylab = "Distance",...) ) t1 <- new("track", x=1:20, y=(1:20)^2) plot(t1) plot(qnorm(ppoints(20)), t1) ## Now a class that inherits from "track", with a vector for data at ## the points setClass("trackData", contains = c("numeric", "track")) tc1 <- new("trackData", t1, rnorm(20)) ## a method for plotting the object ## This method has an extra argument, allowed because ... is an ## argument to the generic function. setMethod("plot", c("trackData", "missing"), function(x, y, maxRadius = max(par("cin")), ...) { plot(x@x, x@y, type = "n", ...) symbols(x@x, x@y, circles = abs(x), inches = maxRadius) } ) plot(tc1) ## Without other methods for "trackData", methods for "track" ## will be selected by inheritance plot(qnorm(ppoints(20)), tc1) ## defining methods for primitive function. ## Although "[" and "length" are not ordinary functions ## methods can be defined for them. setMethod("[", "track", function(x, i, j, ..., drop) { x@x <- x@x[i]; x@y <- x@y[i] x }) plot(t1[1:15]) setMethod("length", "track", function(x)length(x@y)) length(t1) ## Methods for binary operators ## A method for the group generic "Ops" will apply to all operators ## unless a method for a more specific operator has been defined. ## For one trackData argument, go on with just the data part setMethod("Ops", signature(e1 = "trackData"), function(e1, e2) callGeneric([email protected], e2)) setMethod("Ops", signature(e2 = "trackData"), function(e1, e2) callGeneric(e1, [email protected])) ## At this point, the choice of a method for a call with BOTH ## arguments from "trackData" is ambiguous. We must define a method. setMethod("Ops", signature(e1 = "trackData", e2 = "trackData"), function(e1, e2) callGeneric([email protected], [email protected])) ## (well, really we should only do this if the "track" part ## of the two arguments matched) tc1 +1 1/tc1 all(tc1 == tc1)
## examples for a simple class with two numeric slots. ## (Run example(setMethod) to see the class and function definitions) ## methods for plotting track objects ## ## First, with only one object as argument, plot the two slots ## y must be included in the signature, it would default to "ANY" setMethod("plot", signature(x="track", y="missing"), function(x, y, ...) plot(x@x, x@y, ...) ) ## plot numeric data on either axis against a track object ## (reducing the track object to the cumulative distance along the track) ## Using a short form for the signature, which matches like formal arguments setMethod("plot", c("track", "numeric"), function(x, y, ...) plot(cumdist(x@x, x@y), y, xlab = "Distance",...) ) ## and similarly for the other axis setMethod("plot", c("numeric", "track"), function(x, y, ...) plot(x, cumdist(y@x, y@y), ylab = "Distance",...) ) t1 <- new("track", x=1:20, y=(1:20)^2) plot(t1) plot(qnorm(ppoints(20)), t1) ## Now a class that inherits from "track", with a vector for data at ## the points setClass("trackData", contains = c("numeric", "track")) tc1 <- new("trackData", t1, rnorm(20)) ## a method for plotting the object ## This method has an extra argument, allowed because ... is an ## argument to the generic function. setMethod("plot", c("trackData", "missing"), function(x, y, maxRadius = max(par("cin")), ...) { plot(x@x, x@y, type = "n", ...) symbols(x@x, x@y, circles = abs(x), inches = maxRadius) } ) plot(tc1) ## Without other methods for "trackData", methods for "track" ## will be selected by inheritance plot(qnorm(ppoints(20)), tc1) ## defining methods for primitive function. ## Although "[" and "length" are not ordinary functions ## methods can be defined for them. setMethod("[", "track", function(x, i, j, ..., drop) { x@x <- x@x[i]; x@y <- x@y[i] x }) plot(t1[1:15]) setMethod("length", "track", function(x)length(x@y)) length(t1) ## Methods for binary operators ## A method for the group generic "Ops" will apply to all operators ## unless a method for a more specific operator has been defined. ## For one trackData argument, go on with just the data part setMethod("Ops", signature(e1 = "trackData"), function(e1, e2) callGeneric(e1@.Data, e2)) setMethod("Ops", signature(e2 = "trackData"), function(e1, e2) callGeneric(e1, e2@.Data)) ## At this point, the choice of a method for a call with BOTH ## arguments from "trackData" is ambiguous. We must define a method. setMethod("Ops", signature(e1 = "trackData", e2 = "trackData"), function(e1, e2) callGeneric(e1@.Data, e2@.Data)) ## (well, really we should only do this if the "track" part ## of the two arguments matched) tc1 +1 1/tc1 all(tc1 == tc1)
Register an old-style (a.k.a. ‘S3’) class as a formally defined class. Simple usage will be of the form:
setOldClass(Classes)
where Classes
is the character vector that would be the
class
attribute of the S3 object. Calls to
setOldClass()
in the code for a package
allow the class to be used as a slot in formal (S4) classes and in
signatures for methods (see Methods_for_S3).
Formal classes can also contain a registered S3 class (see
S3Part for details).
If the S3 class has a known set of attributes, an
equivalent S4 class can be specified by S4Class=
in the call to
setOldClass()
; see the section “Known Attributes”.
setOldClass(Classes, prototype, where, test = FALSE, S4Class)
setOldClass(Classes, prototype, where, test = FALSE, S4Class)
Classes |
A character vector, giving the names for S3
classes, as they would appear on the right side of an assignment of
the In addition to S3 classes, an object type or other valid data part can be specified, if the S3 class is known to require its data to be of that form. |
S4Class |
optionally, the class definition or the class name
of an S4 class. The new class will have all the slots and other
properties of this class, plus any S3 inheritance implied by
multiple names in the |
prototype , where , test
|
These arguments are currently allowed, but not recommended in typical applications.
|
The name (or each of the names) in Classes
will be defined as an S4 class, extending class oldClass
,
which is the ‘root’ of all old-style classes. S3 classes
with multiple names in their class attribute will have a
corresponding inheritance as formal classes. See the "mlm"
example.
S3 classes have
no formal definition, and therefore no formally defined slots.
If no S4 class is supplied as a model, the class created will be a
virtual class.
If a virtual class (any virtual class) is used for a slot in another class, then the
initializing method for the class needs to put something legal in
that slot; otherwise it will be set to NULL
.
See Methods_for_S3 for the details of method dispatch and inheritance with mixed S3 and S4 methods.
Some S3 classes cannot be represented as an ordinary combination of S4
classes and superclasses, because objects with the same initial
string in the class attribute can have different strings following.
Such classes are fortunately rare. They violate the basic idea of
object-oriented programming and should be avoided.
If you must deal with them, it is still possible to register
such classes as S4 classes, but now the inheritance has to be verified
for each object, and you must call setOldClass
with argument
test=TRUE
.
Many of the widely used S3 classes in the standard R distribution come pre-defined for use with S4. These don't need to be explicitly declared in your package (although it does no harm to do so).
The list .OldClassesList
contains the old-style classes that
are defined by the methods package. Each element of the list is a
character vector, with multiple strings if inheritance is included.
Each element of the list was passed to setOldClass
when
creating the methods package; therefore, these classes can be used
in setMethod
calls, with the inheritance as implied by
the list.
A further specification of an S3 class can be made if the class is guaranteed to have some attributes of known class (where as with slots, “known” means that the attribute is an object of a specified class, or a subclass of that class).
In this case, the call to setOldClass()
can supply an S4 class
definition representing the known structure. Since S4 slots are
implemented as attributes (largely for just this reason), the known
attributes can be specified in the representation of the S4 class.
The usual technique will be to create an S4 class with the desired
structure, and then supply the class name or definition as the
argument S4Class=
to setOldClass()
.
See the definition of class "ts"
in the examples below and
the data.frame
example in Section 10.2 of the reference.
The call to setClass
to create the S4 class can use the same
class name, as here, so long as the call to setOldClass
follows in the same package. For clarity it should be the next
expression in the same file.
In the example, we define "ts"
as a vector structure with a
numeric slot for "tsp"
. The validity of this definition relies
on an assertion that all the S3 code for this class is consistent with
that definition; specifically, that all "ts"
objects will
behave as vector structures and will have a numeric "tsp"
attribute. We believe this to be true of all the base code in R, but
as always with S3 classes, no guarantee is possible.
The S4 class definition can have virtual superclasses (as in
the "ts"
case) if the S3 class is asserted to behave
consistently with these (in the example, time-series objects are
asserted to be consistent with the structure class).
Failures of the S3 class to live up to its asserted
behavior will usually go uncorrected, since S3 classes inherently
have no definition, and the resulting invalid S4 objects can cause
all sorts of grief. Many S3 classes are not candidates for known
slots, either because the presence or class of the attributes are
not guaranteed (e.g., dimnames
in arrays, although these are
not even S3 classes), or because the class uses named components of
a list rather than attributes (e.g., "lm"
). An attribute
that is sometimes missing cannot be represented as a slot, not even
by pretending that it is present with class "NULL"
, because
attributes, unlike slots, can not have value NULL
.
One irregularity that is usually tolerated, however, is to optionally
add other attributes to those guaranteed to exist (for example,
"terms"
in "data.frame"
objects returned by
model.frame
). Validity checks by
validObject
ignore extra attributes; even if this check
is tightened in the future, classes extending S3 classes would likely
be exempted because extra attributes are so common.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10, particularly Section 10.8)
require(stats) ## "lm" and "mlm" are predefined; if they were not this would do it: ## Not run: setOldClass(c("mlm", "lm")) ## End(Not run) ## Define a new generic function to compute the residual degrees of freedom setGeneric("dfResidual", function(model) stop(gettextf( "This function only works for fitted model objects, not class %s", class(model)))) setMethod("dfResidual", "lm", function(model)model$df.residual) ## dfResidual will work on mlm objects as well as lm objects myData <- data.frame(time = 1:10, y = (1:10)^.5) myLm <- lm(cbind(y, y^3) ~ time, myData) ## two examples extending S3 class "lm": class "xlm" directly ## and "ylm" indirectly setClass("xlm", slots = c(eps = "numeric"), contains = "lm") setClass("ylm", slots = c(header = "character"), contains = "xlm") ym1 = new("ylm", myLm, header = "Example", eps = 0.) ## for more examples, see ?\link{S3Class}. ## Not run: ## The code in R that defines "ts" as an S4 class setClass("ts", contains = "structure", slots = c(tsp = "numeric"), prototype(NA, tsp = rep(1,3))) # prototype to be a legal S3 time-series ## and now registers it as an S3 class setOldClass("ts", S4Class = "ts", where = envir) ## End(Not run)
require(stats) ## "lm" and "mlm" are predefined; if they were not this would do it: ## Not run: setOldClass(c("mlm", "lm")) ## End(Not run) ## Define a new generic function to compute the residual degrees of freedom setGeneric("dfResidual", function(model) stop(gettextf( "This function only works for fitted model objects, not class %s", class(model)))) setMethod("dfResidual", "lm", function(model)model$df.residual) ## dfResidual will work on mlm objects as well as lm objects myData <- data.frame(time = 1:10, y = (1:10)^.5) myLm <- lm(cbind(y, y^3) ~ time, myData) ## two examples extending S3 class "lm": class "xlm" directly ## and "ylm" indirectly setClass("xlm", slots = c(eps = "numeric"), contains = "lm") setClass("ylm", slots = c(header = "character"), contains = "xlm") ym1 = new("ylm", myLm, header = "Example", eps = 0.) ## for more examples, see ?\link{S3Class}. ## Not run: ## The code in R that defines "ts" as an S4 class setClass("ts", contains = "structure", slots = c(tsp = "numeric"), prototype(NA, tsp = rep(1,3))) # prototype to be a legal S3 time-series ## and now registers it as an S3 class setOldClass("ts", S4Class = "ts", where = envir) ## End(Not run)
Display the object, by printing, plotting or whatever suits its
class. This function exists to be specialized by methods. The
default method calls showDefault
.
Formal methods for show
will
usually be invoked for automatic printing (see the details).
show(object)
show(object)
object |
Any R object |
Objects from an S4 class (a class defined by a call to
setClass
) will be displayed automatically is if by a
call to show
. S4 objects that occur as attributes of S3
objects will also be displayed in this form; conversely, S3 objects
encountered as slots in S4 objects will be printed using the S3
convention, as if by a call to print
.
Methods defined for show
will only be inherited by simple
inheritance, since otherwise the method would not receive the
complete, original object, with misleading results. See the
simpleInheritanceOnly
argument to setGeneric
and
the discussion in setIs
for the general concept.
show
returns an invisible NULL
.
showMethods
prints all the methods for one or more
functions.
## following the example shown in the setMethod documentation ... setClass("track", slots = c(x="numeric", y="numeric")) setClass("trackCurve", contains = "track", slots = c(smooth = "numeric")) t1 <- new("track", x=1:20, y=(1:20)^2) tc1 <- new("trackCurve", t1) setMethod("show", "track", function(object)print(rbind(x = object@x, y=object@y)) ) ## The method will now be used for automatic printing of t1 t1 ## Not run: [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12] x 1 2 3 4 5 6 7 8 9 10 11 12 y 1 4 9 16 25 36 49 64 81 100 121 144 [,13] [,14] [,15] [,16] [,17] [,18] [,19] [,20] x 13 14 15 16 17 18 19 20 y 169 196 225 256 289 324 361 400 ## End(Not run) ## and also for tc1, an object of a class that extends "track" tc1 ## Not run: [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12] x 1 2 3 4 5 6 7 8 9 10 11 12 y 1 4 9 16 25 36 49 64 81 100 121 144 [,13] [,14] [,15] [,16] [,17] [,18] [,19] [,20] x 13 14 15 16 17 18 19 20 y 169 196 225 256 289 324 361 400 ## End(Not run)
## following the example shown in the setMethod documentation ... setClass("track", slots = c(x="numeric", y="numeric")) setClass("trackCurve", contains = "track", slots = c(smooth = "numeric")) t1 <- new("track", x=1:20, y=(1:20)^2) tc1 <- new("trackCurve", t1) setMethod("show", "track", function(object)print(rbind(x = object@x, y=object@y)) ) ## The method will now be used for automatic printing of t1 t1 ## Not run: [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12] x 1 2 3 4 5 6 7 8 9 10 11 12 y 1 4 9 16 25 36 49 64 81 100 121 144 [,13] [,14] [,15] [,16] [,17] [,18] [,19] [,20] x 13 14 15 16 17 18 19 20 y 169 196 225 256 289 324 361 400 ## End(Not run) ## and also for tc1, an object of a class that extends "track" tc1 ## Not run: [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12] x 1 2 3 4 5 6 7 8 9 10 11 12 y 1 4 9 16 25 36 49 64 81 100 121 144 [,13] [,14] [,15] [,16] [,17] [,18] [,19] [,20] x 13 14 15 16 17 18 19 20 y 169 196 225 256 289 324 361 400 ## End(Not run)
Show a summary of the methods for one or more generic functions, possibly restricted to those involving specified classes.
showMethods(f = character(), where = topenv(parent.frame()), classes = NULL, includeDefs = FALSE, inherited = !includeDefs, showEmpty, printTo = stdout(), fdef) .S4methods(generic.function, class)
showMethods(f = character(), where = topenv(parent.frame()), classes = NULL, includeDefs = FALSE, inherited = !includeDefs, showEmpty, printTo = stdout(), fdef) .S4methods(generic.function, class)
f |
one or more function names. If omitted, all functions will be shown that match the other arguments. The argument can also be an expression that evaluates to a single
generic function, in which
case argument |
where |
Where to find the generic function, if not supplied as an
argument. When |
classes |
If argument |
includeDefs |
If |
inherited |
logical indicating if methods that have been found by
inheritance, so far in the session, will be included and marked as
inherited. Note that an inherited method will not usually appear
until it has been used in this session. See
|
showEmpty |
logical indicating whether methods with no defined
methods matching the other criteria should be shown at all. By
default, |
printTo |
The connection on which the information will be shown; by default, on standard output. |
fdef |
Optionally, the generic function definition to use; if
missing, one is found, looking in |
generic.function , class
|
See |
See methods
for a description of .S4methods
.
The name and package of the generic are followed by the list of signatures for which methods are currently defined, according to the criteria determined by the various arguments. Note that the package refers to the source of the generic function. Individual methods for that generic can come from other packages as well.
When more than one generic function is involved, either as specified or
because f
was missing, the functions are found and
showMethods
is recalled for each, including the generic as the
argument fdef
. In complicated situations, this can avoid some
anomalous results.
If printTo
is FALSE
, the character vector that would
have been printed is returned; otherwise the value is the connection
or filename, via invisible
.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
setMethod
, and GenericFunctions
for other tools involving methods;
selectMethod
will show you the method dispatched for a
particular function and signature of classes for the arguments.
methods
provides method discovery tools for light-weight
interactive use.
require(graphics) ## Assuming the methods for plot ## are set up as in the example of help(setMethod), ## print (without definitions) the methods that involve class "track": showMethods("plot", classes = "track") ## Not run: # Function "plot": # x = ANY, y = track # x = track, y = missing # x = track, y = ANY require("Matrix") showMethods("%*%")# many! methods(class = "Matrix")# nothing showMethods(class = "Matrix")# everything showMethods(Matrix:::isDiagonal) # a non-exported generic ## End(Not run) if(no4 <- is.na(match("stats4", loadedNamespaces()))) loadNamespace("stats4") showMethods(classes = "mle") # -> a method for show() if(no4) unloadNamespace("stats4")
require(graphics) ## Assuming the methods for plot ## are set up as in the example of help(setMethod), ## print (without definitions) the methods that involve class "track": showMethods("plot", classes = "track") ## Not run: # Function "plot": # x = ANY, y = track # x = track, y = missing # x = track, y = ANY require("Matrix") showMethods("%*%")# many! methods(class = "Matrix")# nothing showMethods(class = "Matrix")# everything showMethods(Matrix:::isDiagonal) # a non-exported generic ## End(Not run) if(no4 <- is.na(match("stats4", loadedNamespaces()))) loadNamespace("stats4") showMethods(classes = "mle") # -> a method for show() if(no4) unloadNamespace("stats4")
"signature"
For Method DefinitionsThis class represents the mapping of some of the formal
arguments of a function onto the corresponding classes. It is used for
two slots in the MethodDefinition
class.
Objects can be created by calls of the form new("signature",
functionDef, ...)
. The functionDef
argument, if it is
supplied as a function object, defines the formal names. The other
arguments define the classes. More typically, the objects are
created as side effects of defining methods. Either way, note that
the classes are expected to be well defined, usually because the
corresponding class definitions exist. See the comment on the
package
slot.
.Data
:Object of class "character"
the class names.
names
:Object of class "character"
the
corresponding argument names.
package
:Object of class "character"
the
names of the packages corresponding to the class names. The
combination of class name and package uniquely defines the
class. In principle, the same class name could appear in more
than one package, in which case the package
information
is required for the signature to be well defined.
Class "character"
, from data part.
Class "vector"
, by class "character".
signature(object = "signature")
: see the
discussion of objects from the class, above.
class MethodDefinition
for the use of this class.
These functions return or set information about the individual slots in an object.
object@name object@name <- value slot(object, name) slot(object, name, check = TRUE) <- value .hasSlot(object, name) slotNames(x) .slotNames(x) getSlots(x)
object@name object@name <- value slot(object, name) slot(object, name, check = TRUE) <- value .hasSlot(object, name) slotNames(x) .slotNames(x) getSlots(x)
object |
An object from a formally defined class. |
name |
The name of the slot. The operator
takes a fixed name, which can be unquoted if it is syntactically a
name in the language. A slot name can be any non-empty string, but
if the name is not made up of letters, numbers, and In the case of the |
value |
A new value for the named slot. The value must be valid for this slot in this object's class. |
check |
In the replacement version of |
x |
either the name of a class (as character string), or a class
definition. If given an argument that is neither a character string
nor a class definition, |
The definition of the class specifies all slots directly and indirectly defined for that class. Each slot has a name and an associated class. Extracting a slot returns an object from that class. Setting a slot first coerces the value to the specified slot and then stores it.
Unlike general attributes, slots are not partially matched, and asking for (or trying to set) a slot with an invalid name for that class generates an error.
The @
extraction operator and slot
function themselves do no checking against the class definition,
simply matching the name in the object itself.
The replacement forms do check (except for slot
in the case
check=FALSE
). So long as slots are set without cheating, the
extracted slots will be valid.
Be aware that there are two ways to cheat, both to be avoided but
with no guarantees. The obvious way is to assign a slot with
check=FALSE
. Also, slots in R are implemented as
attributes, for the sake of some back compatibility. The current
implementation does not prevent attributes being assigned, via
attr<-
, and such assignments are not checked for
legitimate slot names.
Note that the "@"
operators for extraction and replacement are
primitive and actually reside in the base package.
The replacement versions of "@"
and slot()
differ in
the computations done to coerce the right side of the assignment to
the declared class of the slot. Both verify that the value provided
is from a subclass of the declared slot class. The slot()
version will go on to call the coerce method if there is one, in
effect doing the computation as(value, slotClass, strict =
FALSE)
. The "@"
version just verifies the relation,
leaving any coerce to be done later (e.g., when a relevant method is
dispatched).
In most uses the result is equivalent, and the "@"
version
saves an extra function call, but if empirical evidence shows that a
conversion is needed, either call as()
before the replacement
or use the replacement version of slot()
.
The "@"
operator and the slot
function extract or
replace the formally defined slots for the object.
Functions slotNames
and getSlots
return respectively the
names of the slots and the classes associated with the slots in the
specified class definition. Except for its extended interpretation of
x
(above), slotNames(x)
is just names(getSlots(x))
.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
@
,
Classes_Details
,
Methods_Details
,
getClass
,
names
.
setClass("track", slots = c(x="numeric", y="numeric")) myTrack <- new("track", x = -4:4, y = exp(-4:4)) slot(myTrack, "x") slot(myTrack, "y") <- log(slot(myTrack, "y")) utils::str(myTrack) getSlots("track") # or getSlots(getClass("track")) slotNames(class(myTrack)) # is the same as slotNames(myTrack) ## Transform such an S4 object to a list, e.g. to "export" it: S4toList <- function(obj) { sn <- slotNames(obj) structure(lapply(sn, slot, object = obj), names = sn) } S4toList(myTrack)
setClass("track", slots = c(x="numeric", y="numeric")) myTrack <- new("track", x = -4:4, y = exp(-4:4)) slot(myTrack, "x") slot(myTrack, "y") <- log(slot(myTrack, "y")) utils::str(myTrack) getSlots("track") # or getSlots(getClass("track")) slotNames(class(myTrack)) # is the same as slotNames(myTrack) ## Transform such an S4 object to a list, e.g. to "export" it: S4toList <- function(obj) { sn <- slotNames(obj) structure(lapply(sn, slot, object = obj), names = sn) } S4toList(myTrack)
The virtual class structure
and classes that
extend it are formal classes analogous to S language structures such
as arrays and time-series.
## The following class names can appear in method signatures, ## as the class in as() and is() expressions, and, except for ## the classes commented as VIRTUAL, in calls to new() "matrix" "array" "ts" "structure" ## VIRTUAL
## The following class names can appear in method signatures, ## as the class in as() and is() expressions, and, except for ## the classes commented as VIRTUAL, in calls to new() "matrix" "array" "ts" "structure" ## VIRTUAL
Objects can be created by calls of the form new(Class, ...)
,
where Class
is the quoted name of the specific class (e.g.,
"matrix"
), and the other arguments, if any, are interpreted as
arguments to the corresponding function, e.g., to function
matrix()
. There is no particular advantage over calling those
functions directly, unless you are writing software designed to work
for multiple classes, perhaps with the class name and the arguments
passed in.
Objects created from the classes "matrix"
and "array"
are unusual, to put it mildly, and have been for some time. Although
they may appear to be objects from these classes, they do not have the
internal structure of either an S3 or S4 class object. In particular,
they have no "class"
attribute and are not recognized as
objects with classes (that is, both is.object
and
isS4
will return FALSE
for such objects).
However, methods (both S4 and S3) can be defined for these
pseudo-classes and new classes (both S4 and S3) can inherit from them.
That the objects still behave as if they came from the corresponding
class (most of the time, anyway) results from special code
recognizing such objects being built into the base code of R.
For most purposes, treating the classes in the usual way will work,
fortunately. One consequence of the special treatment is that these
two classesmay be used as the data part of an S4 class; for
example, you can get away with contains = "matrix"
in a call
to setGeneric
to create an S4 class that is a subclass
of "matrix"
. There is no guarantee that everything will work
perfectly, but a number of classes have been written in this form
successfully.
Note that a class containing "matrix"
or "array"
will
have a .Data
slot with that class. This is the only use of
.Data
other than as a pseudo-class indicating the type of the
object. In this case the type of the object will be the type of the
contained matrix or array. See Classes_Details
for a general
discussion.
The class "ts"
is basically an S3 class
that has been registered with S4, using the
setOldClass
mechanism. Versions of R through 2.7.0
treated this class as a pure S4 class, which was in principal a good
idea, but in practice did not allow subclasses to be defined and had
other intrinsic problems. (For example, setting the
"tsp"
parameters as a slot often fails because the built-in
implementation does not allow the slot to be temporarily
inconsistent with the length of the data. Also, the S4 class
prevented the correct specification of the S3 inheritance for class
"mts"
.)
Time-series objects, in contrast to matrices and arrays, have a valid
S3 class, "ts"
, registered using an S4-style definition (see the
documentation for setOldClass
in the examples section
for an abbreviated listing of how this is done). The S3
inheritance of "mts"
in package stats is also
registered.
These classes, as well as "matrix"
and "array"
should
be valid in most examples as superclasses for new S4 class
definitions.
All of these classes have special S4 methods for
initialize
that accept the same arguments as the basic
generator functions, matrix
,
array
, and ts
, in so far as possible.
The limitation is that a class that has more than one non-virtual
superclass must accept objects from that superclass in the call to
new
; therefore, a such a class (what is called a
“mixin” in some languages) uses the default method for
initialize
, with no special arguments.
The specific classes all extend class "structure"
, directly, and
class "vector"
, by class "structure"
.
Methods are defined to coerce arbitrary objects to
these classes, by calling the corresponding basic function, for
example, as(x, "matrix")
calls as.matrix(x)
.
If strict = TRUE
in the call to as()
, the method
goes on to delete all other slots and attributes other than the
dim
and dimnames
.
Group methods (see, e.g., S4groupGeneric
)
are defined for combinations of structures and vectors (including
special cases for array and matrix), implementing the concept of
vector structures as in the reference. Essentially, structures
combined with vectors retain the structure as long as the
resulting object has the same length. Structures combined with
other structures remove the structure, since there is no
automatic way to determine what should happen to the slots
defining the structure.
Note that these methods will be activated when a package is loaded
containing a class that inherits from any of the structure
classes or class "vector"
.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (For the R version.)
Chambers, John M. (1998) Programming with Data Springer (For the original S4 version.)
Becker, R. A., Chambers, J. M. and Wilks, A. R. (1988) The New S Language. Wadsworth & Brooks/Cole (for the original vector structures).
Class nonStructure, which enforces the alternative model, in which all slots are dropped if any math transformation or operation is applied to an object from a class extending one of the basic classes.
showClass("structure") ## explore a bit : showClass("ts") (ts0 <- new("ts")) str(ts0) showMethods("Ops") # six methods from these classes, but maybe many more
showClass("structure") ## explore a bit : showClass("ts") (ts0 <- new("ts")) str(ts0) showMethods("Ops") # six methods from these classes, but maybe many more
A set of distinct inherited signatures is generated to test inheritance for all the methods of a specified generic function. If method selection is ambiguous for some of these, a summary of the ambiguities is attached to the returned object. This test should be performed by package authors before releasing a package.
testInheritedMethods(f, signatures, test = TRUE, virtual = FALSE, groupMethods = TRUE, where = .GlobalEnv)
testInheritedMethods(f, signatures, test = TRUE, virtual = FALSE, groupMethods = TRUE, where = .GlobalEnv)
f |
a generic function or the character string name of one. By default, all currently defined subclasses of all the method signatures for this generic will be examined. The other arguments are mainly options to modify which inheritance patterns will be examined. |
signatures |
An optional set of subclass signatures to use instead of the relevant
subclasses computed by |
test |
optional flag to control whether method selection is actually tested.
If |
virtual |
should virtual classes be included in the relevant subclasses. Normally not, since only the classes of actual arguments will trigger the inheritance calculation in a call to the generic function. Including virtual classes may be useful if the class has no current non-virtual subclasses but you anticipate your users may define such classes in the future. |
groupMethods |
should methods for the group generic function be included? |
where |
the environment in which to look for class definitions. Nearly always, use the default global environment after attaching all the packages with relevant methods and/or class definitions. |
The following description applies when the optional arguments are
omitted, the usual case.
First, the defining signatures for all methods are computed by calls
to findMethodSignatures
.
From these all the known non-virtual subclasses are found for each
class that appears in the signature of some method.
These subclasses are split into groups according to which class they
inherit from, and only one subclass from each group is retained (for
each argument in the generic signature).
So if a method was defined with class "vector"
for some
argument, one actual vector class is chosen arbitrarily.
The case of "ANY"
is dealt with specially, since all classes
extend it. A dummy, nonvirtual class, ".Other"
, is used to
correspond to all classes that have no superclasses among those being
tested.
All combinations of retained subclasses for the
arguments in the generic signature are then computed.
Each row of the resulting matrix is a signature to be tested by a call
to selectMethod
.
To collect information on ambiguous selections,
testInheritedMethods
establishes a calling handler for the
special signal "ambiguousMethodSelection"
, by setting the
corresponding option.
An object of class "methodSelectionReport"
. The details of
this class are currently subject to change. It has slots
"target"
, "selected"
, "candidates"
, and
"note"
, all referring to the ambiguous cases (and so of length
0 if there were none). These slots are intended to be examined by the
programmer to detect and preferably fix ambiguous method selections.
The object contains in addition slots "generic"
, the name of
the generic function, and
"allSelections"
, giving the vector of labels for all
the signatures tested.
Chambers, John M. (2008) Software for Data Analysis: Programming with R Springer. (Section 10.6 for basics of method selection.)
Chambers, John M. (2009) Class Inheritance in R https://johnmchambers.su.domains/classInheritance.pdf.
## if no other attached packages have methods for `+` or its group ## generic functions, this returns a 16 by 2 matrix of selection ## patterns (in R 2.9.0) testInheritedMethods("+")
## if no other attached packages have methods for `+` or its group ## generic functions, this returns a 16 by 2 matrix of selection ## patterns (in R 2.9.0) testInheritedMethods("+")
The classes described here are used by the R function
trace
to create versions of functions and methods
including browser calls, etc., and also to untrace
the
same objects.
### Objects from the following classes are generated ### by calling trace() on an object from the corresponding ### class without the "WithTrace" in the name. "functionWithTrace" "MethodDefinitionWithTrace" "MethodWithNextWithTrace" "genericFunctionWithTrace" "groupGenericFunctionWithTrace" ### the following is a virtual class extended by each of the ### classes above "traceable"
### Objects from the following classes are generated ### by calling trace() on an object from the corresponding ### class without the "WithTrace" in the name. "functionWithTrace" "MethodDefinitionWithTrace" "MethodWithNextWithTrace" "genericFunctionWithTrace" "groupGenericFunctionWithTrace" ### the following is a virtual class extended by each of the ### classes above "traceable"
Objects will be created from these classes by calls to trace
.
(There is an initialize
method for class
"traceable"
, but you are unlikely to need it directly.)
.Data
:The data part, which will be "function"
for class "functionWithTrace"
, and similarly for the other
classes.
original
:Object of the original class; e.g.,
"function"
for class "functionWithTrace"
.
Each of the classes extends the corresponding untraced class, from the
data part; e.g., "functionWithTrace"
extends "function"
.
Each of the specific classes extends "traceable"
, directly,
and class "VIRTUAL"
, by class "traceable"
.
The point of the specific classes is that objects generated from them,
by function trace()
, remain callable or dispatchable, in
addition to their new trace information.
function trace
validObject()
tests the validity of object
related to
its class definition; specifically, it checks that all slots
specified in the class definition are present and that the object in
the slot is from the required class or a subclass of that class.
If the object is valid, TRUE
is returned; otherwise, an error
is generated, reporting all the validity failures encountered.
If argument test
is
TRUE
, the errors are returned as a character vector rather
than generating an error.
When an object from a class is initialized, the default method for
initialize()
calls validObject
.
A class definition may have a validity method, set by a call to
the function setValidity
, in the package or environment that
defines the class (or via the validity
argument to setClass
). The method
should be a function of one object that returns TRUE
or a character-string
description of the non-validity.
If such a method exists, it will be called from validObject
and any strings from failure will be included in the result or the
error message.
Any validity methods defined for superclasses (from the contains=
argument to setClass
), will also be called.
validObject(object, test = FALSE, complete = FALSE) setValidity(Class, method, where = topenv(parent.frame()) ) getValidity(ClassDef)
validObject(object, test = FALSE, complete = FALSE) setValidity(Class, method, where = topenv(parent.frame()) ) getValidity(ClassDef)
object |
any object, but not much will happen unless the object's class has a formal definition. |
test |
logical; if |
complete |
logical; if |
Class |
the name or class definition of the class whose validity method is to be set. |
ClassDef |
a class definition object, as from
|
method |
a validity method; that is, either |
where |
an environment to store the modified class definition. Should be omitted, specifically for calls from a package that defines the class. The definition will be stored in the namespace of the package. |
Validity testing takes place ‘bottom up’, checking the slots, then the superclasses, then the object's own validity method, if there is one.
For each slot and superclass, the existence of the specified class is
checked.
For each slot, the object in the slot is tested for inheritance from
the corresponding class.
If complete
is TRUE
, validObject
is called
recursively for the object in the slot.
Then, for each of the classes that this class
extends (the ‘superclasses’), the explicit validity method of
that class is called, if one exists. Finally, the validity method of
object
's class is called, if there is one.
validObject
returns TRUE
if the object is valid.
Otherwise a vector of strings describing problems found, except that
if test
is FALSE
, validity failure generates an error,
with the corresponding strings in the error message.
A validity method must be a function of one argument; formally, that
argument should be named object
.
If the argument has a different name, setValidity
makes the
substitution but in obscure cases that might fail, so it's wiser to
name the
argument object
.
A good method checks all the possible errors and returns a character
vector citing all the exceptions found, rather than returning after
the first one.
validObject
will accumulate these errors in its error message
or its return value.
Note that validity methods do not have to check validity of
superclasses: validObject
calls such methods explicitly.
Chambers, John M. (2016) Extending R, Chapman & Hall. (Chapters 9 and 10.)
setClass
;
class classRepresentation
.
setClass("track", slots = c(x="numeric", y = "numeric")) t1 <- new("track", x=1:10, y=sort(stats::rnorm(10))) ## A valid "track" object has the same number of x, y values validTrackObject <- function(object) { if(length(object@x) == length(object@y)) TRUE else paste("Unequal x,y lengths: ", length(object@x), ", ", length(object@y), sep="") } ## assign the function as the validity method for the class setValidity("track", validTrackObject) ## t1 should be a valid "track" object validObject(t1) ## Now we do something bad t2 <- t1 t2@x <- 1:20 ## This should generate an error ## Not run: try(validObject(t2)) setClass("trackCurve", contains = "track", slots = c(smooth = "numeric")) ## all superclass validity methods are used when validObject ## is called from initialize() with arguments, so this fails ## Not run: trynew("trackCurve", t2) setClass("twoTrack", slots = c(tr1 = "track", tr2 ="track")) ## validity tests are not applied recursively by default, ## so this object is created (invalidly) tT <- new("twoTrack", tr2 = t2) ## A stricter test detects the problem ## Not run: try(validObject(tT, complete = TRUE))
setClass("track", slots = c(x="numeric", y = "numeric")) t1 <- new("track", x=1:10, y=sort(stats::rnorm(10))) ## A valid "track" object has the same number of x, y values validTrackObject <- function(object) { if(length(object@x) == length(object@y)) TRUE else paste("Unequal x,y lengths: ", length(object@x), ", ", length(object@y), sep="") } ## assign the function as the validity method for the class setValidity("track", validTrackObject) ## t1 should be a valid "track" object validObject(t1) ## Now we do something bad t2 <- t1 t2@x <- 1:20 ## This should generate an error ## Not run: try(validObject(t2)) setClass("trackCurve", contains = "track", slots = c(smooth = "numeric")) ## all superclass validity methods are used when validObject ## is called from initialize() with arguments, so this fails ## Not run: trynew("trackCurve", t2) setClass("twoTrack", slots = c(tr1 = "track", tr2 ="track")) ## validity tests are not applied recursively by default, ## so this object is created (invalidly) tT <- new("twoTrack", tr2 = t2) ## A stricter test detects the problem ## Not run: try(validObject(tT, complete = TRUE))