Xinlei Mi,
PhD. Candidate,
Department of Biostatistics,
University of Florida
xlmi@ufl.edu
History of the S language.
An S3 class is defined by the special attribute class, a character string vector.
x <- seq(0, 10, 2); y <- x + rnorm(length(x))
dat <- rbind(y, x)
attr(dat, "class") <- "foo"
# class(dat) <- "foo" #### Alternatively, use class()
# dat <- structure(rbind(y, x), class = "foo")
dat
attr(dat, "c.names") <- paste("C", 1:length(x), sep='') # Add new attributes
dat
head(methods(print))
print.foo <- function(x, ...) {
y <- data.frame(matrix(x, nrow(x)))
colnames(y) <- attr(x, "c.names")
cat("Print 'foo' \n")
print(y)
}
print(dat)
Let's take a quick example to compare traditional programming with OOP.
The $BMI$ is a measurement of thinness or obesity. And $BMI = \frac{w}{h^2}$ where $w$ is the weight and $h$ is the size.
### Traditional programming, BMI
weight <- 62
size <- 1.70
(BMI <- weight/size**2)
### Traditional programming, my BMI
weightMe <- 62
sizeMe <- 1.70
(BMIMe <- weightMe/sizeMe**2)
### Traditional programming, his BMI
weightHim <- 85
sizeHim <- 1.84
(BMIHim <- weightMe/sizeHim**2)
### Definition of an object BMI
setClass("BMI", slots = list(weight = "numeric", size = "numeric"))
setMethod("show", "BMI",
function(object) {
cat("BMI =", object@weight/object@size**2, " \n")
}
)
(myBMI <- new("BMI", weight = 62, size = 1.70))
(hisBMI <- new("BMI", weight = 85, size = 1.84))
(weight <- "hello")
new("BMI", weight="hello", size=1.70)
(sizeMe <- -1.70)
### Object programming, control
setValidity("BMI",
function(object) {
if (object@size < 0) {
return("Negative size not accepted. ")
} else TRUE
}
)
new("BMI", weight = 62, size = -1.7)
### Definition of the heir
setClass("BMIplus", slots = list(sex = "character"), contains = "BMI")
she <- new("BMIplus", size = 1.65, weight = 52, sex = "Female")
she
Object programming "forces" the programmer to have a preliminary reflection. It is less possible to write "quick-and-dirty" code, a programming plan is almost essential. In particular:
An object is a coherent set of variables and functions which revolve around a central concept. Formally, an object is defined through three elements:
Slots are simply typed variables. A typed variable is a variable whose nature has been fixed.
We distinguish 4 types of operations that can be applied on objects:
A good drawing is better than a long discourse.
# ------------------------------------------
# | BMI | --------------------
# |----------------------------------------| | BMIplus |
# | Slots | | |------------------|
# |--------------- | | Slots | |
# | weight: numeric | <--- |--------- |
# | size: numeric | | sex: character |
# |----------------------------------------| |------------------|
# | Methods | | | Methods| |
# |--------------- | |--------- |
# | NULL <- show(object: BMI) | --------------------
# ------------------------------------------
This problem can be cut into three objects:
Example: $$week = (1, 2, 4, 5, 7)\ \ \ \ \ traj = \left( \begin{array}{lllll} 15 & 15.1 & 15.2 & 15.2 & 14.9 \\ 16 & 15.9 & 16 & 16.4 & 16.6 \\ 15.2 & 15.2 & 15.3 & 15.3 & 15.5 \\ 15.7 & 15.6 & 15.8 & 16 & 15.7 \end{array} \right) $$
A ptGroup object is a set of groups. For example, the groups could be M={I1, I3} and F={I2, I4}. It is undoubtedly simpler to consider them as a vector with length the patients' number: {A, B, A, B}.
Example: $$nbGroups = 2\ \ \ \ \ group = \left( \begin{array}{c} M \\ F \\ M \\ F \\ \end{array} \right)$$
Considering a set of BMI trajectories, several types of groups might possibly be interesting.
Example: $$times = (1, 2, 4, 5, 7)\ \ \ \ \ traj = \left( \begin{array}{lllll} 15 & 15.1 & 15.2 & 15.2 & 14.9 \\ 16 & 15.9 & 16 & 16.4 & 16.6 \\ 15.2 & 15.2 & 15.3 & 15.3 & 15.5 \\ 15.7 & 15.6 & 15.8 & 16 & 15.7 \end{array} \right) $$ $$groupList = \left( \begin{array}{l} nbGroups = 3 \\ part = \left(\begin{array}{c} Y \\ N \\ U \\ Y \\ \end{array}\right) \\ \end{array} \right), \left( \begin{array}{l} nbGroups = 2 \\ part = \left(\begin{array}{c} M \\ F \\ M \\ F \\ \end{array}\right) \\ \end{array} \right)$$
Here is the schedule of our program:
# -------------------------- ----------------------
# | bmiTraj | | ptGroup |
# -------------------------- ----------------------
# | Slots | week | | Slots | nbGroups |
# --------- traj | --------- group |
# -------------------------- ----------------------
# | Methods | countMissing | | | Methods |
# ----------- print | ----------------------
# | imputation | ^
# ----------------------- |
# /\ |
# || |
# ---------------------------
# | bmiGroups |
# ---------------------------
# | Slots | |
# --------| groupList |
# ---------------------------
# | Methods | |
# ----------- print |
# ---------------------------
In most object languages, the definition of the object contains the slot and the methods.
In R, the definition contains only the slot. The methods are specified afterwards.
The first stage is to define the slots of the object itself. That is done by using the function setClass.
setClass(
Class = "bmiTraj",
slots = list(
week = "numeric",
traj = "matrix"
)
)
When a class exists, we can create an object of its class using the constructor 'new':
new(Class = "bmiTraj")
# new(Class = "bmiTraj", week = c(1, 3, 4))
# new(Class = "bmiTraj", week = c(1, 3), traj = matrix(1:4, 2, 2))
# Three doctors take part to the study. Bob, Vic and Ana
bmiBob <- new(Class = "bmiTraj")
bmiVic <- new(
Class = "bmiTraj",
week = c(1, 3, 4, 5),
traj = rbind(c(15, 15.1, 15.2, 15.2),
c(16, 15.9, 16, 16.4),
c(15.2, NA, 15.3, 15.3),
c(15.7, 15.6, 15.8, 16))
)
bmiAna <- new(
Class = "bmiTraj",
week = c(1:10, 6:16*2),
traj = rbind(matrix(seq(16, 19, length = 21), 50, 21, byrow = TRUE),
matrix(seq(15.8, 18, length = 21), 30, 21, byrow = TRUE)) + rnorm(21*80, 0, 0.2)
)
bmiVic@week
bmiVic@week <- c(1, 2, 4, 5)
bmiVic
setClass(
Class = "bmiTrajNew",
slots = list(
week = "numeric",
traj = "matrix"
),
prototype = prototype(week = 1, traj = matrix(0))
)
One can remove a class using removeClass:
removeClass("bmiTrajNew")
new("bmiTrajNew")
The following functions allow the program to see the contents or the structure of the objects
slotNames("bmiTraj")
getSlots("bmiTraj")
getClass("bmiTraj")
One of the interesting characteristics of object programming is to be able to define functions which will adapt their behavior to the object.
size <- rnorm(10, 1.70, 0.1)
weight <- rnorm(10, 70, 5)
group <- as.factor(rep(c("A", "B"), 5))
options(repr.plot.width=7, repr.plot.height=3)
par(mfrow = 1:2)
plot(size ~ weight)
plot(size ~ group)
For that, one uses the function setMethod. It takes three arguments:
setMethod(f = "plot", signature = "bmiTraj",
definition = function(x, y, ...) {
matplot(x@week, t(x@traj), xaxt="n", type="l", ylab="", xlab="", pch=1)
axis(1, at=x@week)
}
)
par(mfrow = 1:2); plot(bmiVic); plot(bmiAna)
# Note: during the redefinition of a function, R imposes to use the same arguments as the function in question.
# To know the arguments of the 'plot', one can use 'args'
args(plot)
args(print)
setMethod("print", "bmiTraj",
function(x, ...) {
cat("*** Class bmiTraj, method Print *** \n")
cat("* Week = "); print(x@week)
cat("* Traj = \n"); print(x@traj)
cat("******* End Print (bmiTraj) ******* \n")
}
)
print(bmiVic)
setMethod("show", "bmiTraj",
function(object) {
cat("*** Class bmiTraj, method show *** \n")
cat("* Week = "); print(object@week)
nrowShow <- min(10, nrow(object@traj))
ncolShow <- min(10, ncol(object@traj))
cat("* Traj (limited to a matrix 10x10) = \n")
print(formatC(object@traj[1:nrowShow, 1:ncolShow]), quote = FALSE)
cat("******* End Show (bmiTraj) ******* \n")
}
)
bmiAna
new("bmiTraj")
setMethod("show", "bmiTraj",
function(object) {
cat("*** Class bmiTraj, method show *** \n")
cat("* Week = "); print(object@week)
nrowShow <- min(10, nrow(object@traj))
ncolShow <- min(10, ncol(object@traj))
cat("* Traj (limited to a matrix 10x10) = \n")
if(length(object@traj) != 0)
print(formatC(object@traj[1:nrowShow, 1:ncolShow]), quote = FALSE)
cat("******* End Show (bmiTraj) ******* \n")
}
)
new("bmiTraj")
We now need to define a new method that is specific to bmiTraj. Therefore, it is necessary for us to declare it. This can be done by using the function setGeneric. This function requires two arguments:
setGeneric(name = "countMissing", def = function(object) standardGeneric("countMissing"))
setMethod(
f = "countMissing",
signature = "bmiTraj",
definition = function(object) return(sum(is.na(object@traj)))
)
countMissing(bmiVic)
There is no control over the existence of a setGeneric: if a setGeneric existed, the new definition destroys the old one. A redefinition is often a mistake. One can "lock" the function using lockBinding.
Our class becomes more complex. It is time to take a little break and to admire our work.
showMethods(classes = "bmiTraj")
# getMethod enables to see the definition (the contents of the body function) of a method for a given object
getMethod(f = "plot", signature = "bmiTraj")
getMethod(f = "plot", signature = "bmiTraj")
existsMethod(f = "plot", signature = "bmiTraj")
existsMethod(f = "plot", signature = "bmiTrej")
Constructions are some tools which enable to build a correct object:
The inspector is there to control that there is no internal inconsistency in the object. One gives it rules, then, at each object creation, it will check that the object follows the rules.
setClass(
Class = "bmiTraj",
slots = list(week = "numeric", traj = "matrix"),
validity = function(object) {
cat("--- bmiTraj: inspector --- \n")
if(length(object@week) != ncol(object@traj))
stop("[bmiTraj: validation] the number of weeks does not correspond to the number of columns of the matrix")
return(TRUE)
}
)
new(Class = "bmiTraj", week = 1:2, traj = matrix(1:2, ncol = 2))
new(Class = "bmiTraj", week = 1:3, traj = matrix(1:2, ncol = 2))
# The inspector will not be called after the creation of the object
bmiPoppy <- new(Class = "bmiTraj", week = 1, traj = matrix(1))
(bmiPoppy@week <- 1:3)
setMethod(f = "initialize", signature = "bmiTraj",
definition = function(.Object, week, traj) {
cat("--- bmiTraj: initializator --- \n")
rownames(traj) <- paste("I", 1:nrow(traj), sep='')
.Object@traj <- traj
.Object@week <- week
return(.Object)
}
)
new(Class = "bmiTraj", week = c(1, 2, 4, 5), traj = matrix(1:8, nrow = 2))
new(Class = "bmiTraj", week = c(1, 2, 4), traj = matrix(1:8, nrow = 2))
# To use an initializator and an inspector in the same object, it is thus necessary to call "manually" the inspector
setMethod(f = "initialize", signature = "bmiTraj",
definition = function(.Object, week, traj) {
cat("--- bmiTraj: initializator --- \n")
if(!missing(traj)) {
colnames(traj) <- paste("T", week, sep='')
rownames(traj) <- paste("I", 1:nrow(traj), sep='')
.Object@traj <- traj
.Object@week <- week
validObject(.Object) # call of the inspector
}
return(.Object)
}
)
new(Class = "bmiTraj", week = c(1, 2, 48), traj = matrix(1:8, nrow = 2))
Aware that new is not a friendly function, the 'nicer' programmer would add user friendly constructors.
tr <- bmiTraj <- function(week, traj) {
cat("----- bmiTraj: constructor ----- \n")
new(Class = "bmiTraj", week = week, traj = traj)
}
bmiTraj(week = c(1, 2, 4), traj = matrix(1:6, ncol=3))
tr <- bmiTraj <- function(week, traj) {
if(missing(week)) week <- 1:ncol(traj)
cat("----- bmiTraj: constructor ----- \n")
new(Class = "bmiTraj", week = week, traj = traj)
}
bmiTraj(traj = matrix(1:8, ncol=4))
Contrary to the initializator, one can define several constructors. Always under the assumption that the BMI increases by 0.1 every week, on can define regularBmiTraj:
regularBmiTraj <- function(nbWeek, BMIinit) {
traj <- outer(BMIinit, 1:nbWeek, function(init, week) return(init+0.1*week))
week <- 1:nbWeek
return(new(Class = "bmiTraj", week = week, traj = traj))
}
regularBmiTraj(nbWeek = 3, BMIinit = 14:16)
Note that the two constructors both call upon the initializator. Hence it's important to define a global initializator that can deal with all the cases.
During the construction of an object, there are three places where it is possible to carry out operations: in the construction's function, in the initializator and in the inspector. In order not to mix everything, it is thus preferable to specialize each one of these operators and to reserve each one precise tasks. Here is a possibility:
Another possibility, suggested by some (high level) programmers, is to NOT use the initializator at all and let the default initializator (more efficient) to be called. The construction function will do all the preparation.
Using @ apart from a method is bad. However, it is necessary to be able to recover the values of slots. This is the role of accessors.
A getter is a method which returns the value of a slot.
setGeneric("getWeek", function(object) standardGeneric("getWeek"))
setMethod("getWeek", "bmiTraj", function(object) return(object@week))
getWeek(bmiVic)
setGeneric("getTraj", function(object) standardGeneric("getTraj"))
setMethod("getTraj", "bmiTraj", function(object) return(object@traj))
getTraj(bmiVic)
A setter is a method which assigns a value to a slot.
setGeneric("setWeek<-", function(object, value) standardGeneric("setWeek<-"))
setReplaceMethod(f = "setWeek", signature = "bmiTraj",
definition = function(object, value) {
object@week <- value
return(object)
}
)
getWeek(bmiVic)
setWeek(bmiVic) <- 1:3
getWeek(bmiVic)
setMethod(
f = "[",
signature = "bmiTraj",
definition = function(x, i, j, drop) {
if(i == "week") return(x@week)
if(i == "traj") return(x@traj)
}
)
bmiVic["week"]
bmiVic["traj"]
setReplaceMethod(
f = "[",
signature = "bmiTraj",
definition = function(x, i, j, value) {
if(i == "week") x@week <- value
if(i == "traj") x@traj <- value
validObject(x)
return(x)
}
)
bmiVic["week"] <- 2:5
bmiVic["week"]
When shall we use 'get', @ or [?
Next steps include signatures, inheritance and some other advanced concepts.
We made our first object. The following is more about interactions between objects.
It's an example. And we will only define the part we need.
setClass(
Class = "ptGroup",
slots = list(
nbGroups = "numeric",
group = "factor"
)
)
setGeneric("getNbGroups", function(object) standardGeneric("getNbGroups"))
setMethod("getNbGroups", "ptGroup", function(object) return(object@nbGroups))
setGeneric("getGroup", function(object) standardGeneric("getGroup"))
setMethod("getGroup", "ptGroup", function(object) return(object@group))
groupVic <- new(Class = "ptGroup", nbGroups = 2, group = factor(c("A", "B", "A", "B")))
groupAna <- new(Class = "ptGroup", nbGroups = 2, group = factor(rep(c("A", "B"), c(50, 30))))
setGeneric("test", function(x, y, ...) standardGeneric("test"))
setMethod("test", "numeric", function(x, y, ...) cat("x is numeric =", x, "\n"))
test(3.17)
test("E")
setMethod("test", "character", function(x, y, ...) cat("x is character =", x, "\n"))
test("E")
# More complicated, we wish that test shows a different behavior if one combines a numeric and a character.
setMethod(
f = "test",
signature = c(x = "numeric", y = "character"),
definition = function(x, y, ...) {
cat("more complicated: ")
cat("x is numeric =", x, "AND y is a character =", y, "\n")
}
)
test(3.2, "E")
test(3.2)
test("E")
Back to our half real example. In the same way that we defined 'plot' for the signature bmiTraj, we now will define 'plot' for the signature c("bmiTraj", "ptGroup"):
options(repr.plot.width=7, repr.plot.height=3)
par(mfrow = c(1, 2))
plot(bmiVic); plot(bmiAna)
setMethod(
f = "plot",
signature = c(x = "bmiTraj", y = "ptGroup"),
definition = function(x, y, ...) {
matplot(x@week, t(x@traj[y@group == levels(y@group)[1], ]), ylim = range(x@traj, na.rm = TRUE),
xaxt = "n", type = "l", ylab = "", xlab = "", col = 2)
for(i in 2:y@nbGroups) {
matlines(x@week, t(x@traj[y@group == levels(y@group)[i], ]), xaxt = "n", type = "l", col = i+1)
}
axis(1, at = x@week)
}
)
par(mfrow = c(1, 2))
plot(bmiVic, groupVic)
plot(bmiAna, groupAna)
showMethods(test)
test(1, TRUE)
setMethod(
f = "test",
signature = c(x = "numeric", y = "missing"),
definition = function(x, y, ...) cat("x is numeric =", x, "and y is 'missing' \n")
)
test(3.17)
test(3.17, "E")
test(3.17, TRUE)
# -----------------------
# | ANY |
# -----------------------
# ^ ^
# | |
# ----------------- -----------------
# | Father A | | Father B |
# ----------------- -----------------
# ^ ^ ^
# ----------- ----------- -----------
# | Son A1 | | Son A2 | | Son B1 |
# ----------- ----------- -----------
# ^
# --------------
# | Gd son A1a |
# --------------
We want to define bmiGroups as heiress of bmiTraj. For that, we have to declare the object adding the argument contains followed by the name of the father class.
setClass(
Class = "bmiGroups",
slots = list(groupList = "list"),
contains = "bmiTraj"
)
bgLisa <- new("bmiGroups")
bgLisa
Why is it?
unclass(bgLisa)
Heritage is a strenth, but it can lead to strange results.
groupVic2 <- new("ptGroup", nbGroups = 3, group = factor(c("A", "C", "C", "B")))
bgVic <- new(
Class = "bmiGroups",
week = c(1, 3, 4, 5),
traj = bgVic@traj,
groupList = list(groupVic, groupVic2)
)
getMethod("initialize", "bmiGroups")
existsMethod("initialize", "bmiGroups")
hasMethod("initialize", "bmiGroups")
selectMethod("initialize", "bmiGroups")
bmiGroups used the initializator of bmiTraj and caused errors.
setMethod("initialize", "bmiGroups",
function(.Object, week, traj, groupList) {
cat("---- groupList: initializator ---- \n")
if(!missing(traj)) {
.Object@week <- week
.Object@traj <- traj
.Object@groupList <- groupList
}
return(.Object)
}
)
bgVic <- new(
Class = "bmiGroups",
week = c(1, 3, 4, 5),
traj = bmiVic@traj,
groupList = list(groupVic, groupVic2)
)
print(bgVic)
setMethod(
f = "print",
signature = "bmiGroups",
definition = function(x, ...) {
callNextMethod() #### callNextMethod()
cat("the object also contains", length(x@groupList), "groups. \n")
cat("**** Fine of print (bmiGroups) **** \n")
return(invisible())
}
)
print(bgVic)
callNextMethod can either take explicit arguments, or no argument at all. In this case, the arguments which were given to the current method are completely shifted to the following method.
Whose method is the following one? Here lies all the difficulty and the ambiguity of callNextMethod.
Example: consider a class A that we program. Let us assume A inherits from class B, a class that somebody else programmed. Which is the method following initialize for A? It all depends. As A inherits, R seeks in the order:
The use of callNextMethod should be limited.
When an object inherits from another, we can require that it adopts temporaily the behavior which its father would have. For that, it is possible to transform it into an object of the class of its father by using 'as'.
print(as(bgVic, "bmiGroups"))
# That will be useful to us in the definition of 'show for bmiGroups, no need to use callNextMethod
setMethod(
f = "show",
signature = "bmiGroups",
definition = function(object) {
show(as(object, "bmiTraj")) ## Instead of callNextMethod, use 'as'
lapply(object@groupList, show)
}
)
# bgVic
We can check if an object is the heir of another by using "is".
is(bmiVic, "bmiGroups")
is(bgVic, "bmiTraj")
Lastly, "as<-" enables to modify the slot which an object inherits from its father. as(objectSon, "ClassFather") <- objectFather affects the contents of the slots that objectSon inherits from its father.
bgAna <- new("bmiGroups")
as(bgAna, "bmiTraj") <- bmiAna
bgAna
In the case of a heritage, 'as' and 'is' are defined "naturally", as we have just seen before. It is also possible to specify them "manually".
For example, the class bmiGroups contains a list of ptGroup's. It does not inherit directly from ptGroup.
This can be done with the instruction setIs. setIs is a method which takes four arguments
setIs(
class1 = "bmiGroups",
class2 = "ptGroup",
coerce = function(from, to) {
numberGroups <- sapply(from@groupList, getNbGroups)
Smallest <- which.min(numberGroups)
to <- new("ptGroup")
to@nbGroups <- getNbGroups(from@groupList[[Smallest]])
to@group <- getGroup(from@groupList[[Smallest]])
return(to)
}
)
is(bgVic, "ptGroup")
as(bgVic, "ptGroup")
A warning appears. R indicates that 'as<-' is not defined.
In our case, 'as<-' is the operator used to modify bmiGroups whereas it is regarded as "ptGroup".
setIs(class1 = "bmiGroups", class2 = "ptGroup",
coerce = function(from, to) {
numberGroups <- sapply(from@groupList, getNbGroups)
Smallest <- which.min(numberGroups)
to <- new("ptGroup")
to@nbGroups <- getNbGroups(from@groupList[[Smallest]])
to@group <- getGroup(from@groupList[[Smallest]])
return(to)
},
replace = function(from, value) {
numberGroups <- sapply(from@groupList, getNbGroups)
Smallest <- which.min(numberGroups)
from@groupList[[Smallest]] <- value
return(from)
}
)
as(bgVic, "ptGroup")
as(bgVic, "ptGroup") <- groupVic2
# bgVic
It happens that classes are close to each other without one being the extension of the other.
For example, we can conceive two types of ptGroup: ptGroup which "labels" individuals without judging them and those which evaluate individuals. The first type of ptGroup will not be ordered (same as ptGroup) and the second type of ptGroup will be ordered (e.g., low/medium/high). Slots of the second class will be nbGroups, an integer which indicates the number of modalities and part, an ordered variable.
One can use a virtual class instead of programming them twice.
setClass(
Class = "ptGroupFather",
slots = list(nbGroups = "numeric"),
contains = "VIRTUAL"
)
new("ptGroupFather")
setClass(Class = "ptGroupSimple",
slots = list(part = "factor"),
contains = "ptGroupFather"
)
setClass(Class = "ptGroupEval",
slots = list(part = "ordered"),
contains = "ptGroupFather"
)
setGeneric("nbMultTwo", function(object) {standardGeneric("nbMultTwo")})
setMethod("nbMultTwo", "ptGroupFather", function(object) {object@nbGroups <- object@nbGroups*2; return(object)})
a <- new("ptGroupSimple", nbGroups = 3, part = factor(LETTERS[c(1, 2, 3, 2, 2, 1)]))
nbMultTwo(a)
# b <- new("ptGroupEval", nbGroups = 5, part = ordered(LETTERS[c(1, 5, 3, 4, 2, 4)]))
# nbMultTwo(b)
Reference classes (or RC for short) are the newest OO system in R. They were introduced in version 2.12. They are fundamentally different to S3 and S4 because:
RC methods belong to objects, not functions
RC objects are mutable: the usual R copy-on-modify semantics do not apply
These properties make RC objects behave more like objects do in most other programming languages, e.g., Python, Ruby, Java, and C#. Reference classes are implemented using R code: they are a special S4 class that wraps around an environment.
Creating a new RC class is similar to creating a new S4 class, but you use setRefClass() instead of setClass().
student <- setRefClass("student")
student$new()
setRefClass() also accepts a list of name-class pairs that define class fields (equivalent to S4 slots). Additional named arguments passed to new() will set initial values of the fields. You can get and set field values with $
student <- setRefClass("student",
fields = list(Age = "numeric"))
Bob <- student$new(Age = 11)
cat("Bob is", Bob$Age, "year old. \n")
Bob$Age <- 12
cat("Bob is", Bob$Age, "year old. \n")
Note that RC objects are mutable, i.e., they have reference semantics, and are not copied-on-modify.
One can make a copy of an RC object by using copy() and make modifications.
Bob$Age <- 11
Mary <- Bob
Mary$Age <- 20
cat("Mary' is", Mary$Age, "year old. \n")
cat("Bob is", Bob$Age, "year old. \n")
Bob$Age <- 11
Mary <- Bob$copy()
Mary$Age <- 20
cat("Mary' is", Mary$Age, "year old. \n")
cat("Bob is", Bob$Age, "year old. \n")
Methods should be defined within the class definition (different from S4). And values can be reached and modified using <<-.
student <- setRefClass("student",
fields = list(Age = "numeric"),
methods = list(
grow = function(x = 1) {
Age <<- Age + x
},
setAge = function(x) {
Age <<- x
}
)
)
Bob <- student$new(Age = 11)
Bob$grow()
cat("Bob is", Bob$Age, "year old. \n")
Bob$setAge(11)
cat("Bob is", Bob$Age, "year old. \n")
One can use contains to inherit from an RC.
studentPlus <- setRefClass("studentPlus",
contains = "student",
methods = list(
setAge = function(x) {
if(x < 0) stop("Age can't be under 0. ")
Age <<- x
}
))
Bob <- studentPlus$new(Age = 11)
Bob$grow(2)
cat("Bob is", Bob$Age, "year old. \n")
Bob$setAge(-1)