Classes, methods, and functions

Một phần của tài liệu Financial risk modelling and portfolio optimization with r second edition (Trang 27 - 37)

In this section, a concise introduction to the three flavors of class and method defi- nitions inRis provided. The first class and method mechanism is referred to asS3, the second asS4, and the third as reference class (RC). Because theS4and refer- ence class mechanisms were included inRat a later stage in its development cycle (made available since versions 1.4.0 and 2.12.0, respectively),S3classes and meth- ods are sometimes also called old-style classes and methods. Detailed and elaborate accounts of these class and method schemes are provided in Becker et al. (1988) and Chambers and Hastie (1992) forS3, and Chambers (1998, 2008) forS4. Aside from these sources, the manual pages forS3andS4classes and methods can be inspected by?Classesand?Methods, respectively. Reference classes are documented in their associated help page?ReferenceClasses. The evolution of and distinction between these three object-oriented (OO) programming incarnations is described in Chambers (2014, 2016). The need to familiarize oneself with these class and method concepts is motivated by the fact that nowadays contributedRpackages utilize either one or the other concept and in some packages a link between the class and method definitions of either kind is established. It should be noted that there are alsoRpack- ages in which neither object-oriented programming concept has been employed at all in the sense of new class and/or method definitions, and such packages can be viewed as collections of functions only.

Before each of the three concepts is described, the reader will recall that everything inRis an object, that a class is the definition of an object, and that a method is a function by which a predefined calculation/manipulation on the object is conducted.

Furthermore, there are generic functions forS3andS4objects which have the sole purpose of determining the class of the object and associating the appropriate method with it. If no specific method can be associated with an object, a default method will be called as a fallback. Generic functions for S3andS4objects can therefore be viewed as an umbrella under which all available class-specific methods are collected.

The difference between S3andS4 classes/methods lies in how a certain class is associated with an object and how a method is dispatched to it.

BecauseRis a dialect of the S language,S3objects, classes, and methods have been available since the very beginning ofR, almost 20 years ago. The assignment

k k of a class name and the method dispatch in this scheme are rather informal and hence

very simple to implement. No formal requirements on the structure of anS3class object are necessary, it is just a matter of adding a class attribute to an object. How swiftly such an attribute can be added to an object and/or changed is shown in the following in-line example:

> x <- 1:5

> x

[1] 1 2 3 4 5

> class(x) [1] "integer"

> xchar <- x

> class(xchar) <- "character"

> class(xchar) [1] "character"

> xchar

[1] "1" "2" "3" "4" "5"

Noteworthy in this example are the different shapes whenxandxcharare printed.

In the former case the object is printed as a numeric vector, and in the latter as a character vector indicated by quotation marks. This observation directly leads on to how method dispatching is accomplished within the S3 framework. Here, a sim- ple naming convention is followed: foo()methods for objects of class barare calledfoo.bar(). When such a function is not defined, theS3method dispatch mechanism searches for a function foo.default(). The available methods for computing the mean of an object can be taken as an example:

> mean

function (x, ...) UseMethod("mean")

<bytecode: 0x34956f0>

<environment: namespace:base>

> methods("mean")

[1] mean.Date mean.default

[3] mean.difftime mean.POSIXct

[5] mean.POSIXlt mean.simple_sparse_array*

[7] mean.simple_triplet_matrix*

see "?methods" for accessing help and source code

Here,mean()is a generic function and the defined methods formean.bar()are returned by themethods()function. As one can see from the output, apart from the default, methods for computing the mean of quite a few other classes of objects have been defined. By now, it should be apparent thatS3classes and methods can best be described as a naming convention, but fall short of what one assumes under the rubric of a mature object-oriented programming approach. Hence, in Chambers (2014)S3 should be viewed as an object-basedfunctional programming scheme rather than an object-orientedone. A major pitfall ofS3classes and methods is that no validation process exists for assessing whether an object claimed to be of a certain class really

k k belongs to it or not. Sticking to our previous example, this is exhibited by trying to

compute the means forxandxchar:

> mean(x) [1] 3

> mean(xchar) [1] NA

Given thatxis of typeinteger, the default method for computing the mean is invoked. Because, there is no methodmean.character(), the default method is also called forxchar. However, this default method tests whether the argument is either numeric or logical, and because this test fails for xchar, anNAvalue is returned and the associated warning is pretty indicative of why such a value has been returned. Just for exemplary purposes, one could define amean()method for objects of classcharacterin the sense that the average count of characters in the strings is returned, as shown next:

> mean.character <- function(x, ...){

+ ans <- mean(nchar(x, ...))

+ ans

+ }

> mean(xchar) [1] 1

However, its simplicity and quite powerful applicability are points in favor of the S3system.

S4classes offer a rigorous definition of an object by demanding that any valid ob- ject must be compliant with the specified class structure. Recall that forS3classes no formal testing of the correct contents of an object belonging to a certain class is required. The introduction of a more formal class mechanism is, however, associ- ated with a cost: complexity. Now it is no longer sufficient to assign a certain object with a class attribute and define methods by adhering to thefoo.bar()naming convention, but rather the handling ofS4classes and methods is accomplished by a set of functions contained in themethodspackage, which is included in the baseR installation. The most commonly encountered ones are:

•setClass()for defining a newS4class;

•new()for creating an object of a certain class;

•setGeneric()for defining a function as generic;

•setMethods()for defining a method for a certain class;

•as()andsetAs()for coercing an object of one class to another class;

•setValidity()andvalidObject()for validating the appropriateness of an object belonging to a certain class;

k k

•showClass(), getClass(), showMethods(), findMethods(), andgetMethods()for displaying the definition/availability ofS4classes and methods;

•slot(),getSlots(),@for extracting elements from an object.

The following in-line examples show (i) how a class for portfolio weights can be defined, (ii) how these objects can be validated, and (iii) how methods can be created for objects of this kind. A more elaborate definition can certainly be designed, but the purpose of these code examples is to give the reader an impression of howS4classes and methods are handled.

First, a classPortWgtis created:

> setClass("PortWgt",

+ representation(Weights = "numeric",

+ Name = "character",

+ Date = "character",

+ Leveraged = "logical",

+ LongOnly = "logical"))

> showClass("PortWgt")

Class "PortWgt" [in ".GlobalEnv"]

Slots:

Name: Weights Name Date Leveraged LongOnly

Class: numeric character character logical logical

The portfolio weight class is defined in terms of a numeric vectorWeightsthat will contain the portfolio weights, a character stringNamefor naming the portfolio associated with this weight vector, as well as a date reference,Date. In addition to these slots, the kind of portfolio is characterized: whether it is of the long-only kind and/or whether leverage is allowed or not. This is accomplished by including the two logical slotsLeveragedandLongOnly, respectively.

At this stage, objects of classPortWgtcould in principle already be created by utilizingnew():

> P1 <- new("PortWgt", Weights = rep(0.2, 5), + Name = "Equal Weighted",

+ Date = "2001-03-31",

+ LongOnly = TRUE,

+ Leveraged = FALSE)

However, a constructor function is ordinarily provided for creating these objects.

Within the function body some measures for safeguarding the appropriateness of the user-provided input can already be taken into account, but this can also be imple- mented by means of a specific validation function.

> PortWgt <- function(Weights, Name, Date = NULL,

+ LongOnly = TRUE, Leveraged = FALSE){

+ Weights <- as.numeric(Weights)

k k

+ Name <- as.character(Name)

+ if(is.null(Date)) Date <- as.character(Sys.Date()) + ans <- new("PortWgt", Weights = Weights, Name = Name,

+ Date = Date, LongOnly = LongOnly,

+ Leveraged = Leveraged)

+ ans

+ }

> P2 <- PortWgt(Weights = rep(0.2, 5), + Name = "Equal Weighted")

One of the strengths of S4is its validation mechanism. In the above example, for instance, an object of classPortWgtcould have been created for a long-only portfolio whereby some of the weights could have been negative, or a portfolio that should not be leveraged but whose absolute weight sum could be greater than unity.

In order to check whether the arguments supplied in the constructor function do not violate the class specification from a content point of view, the following validation function is specified, mostly for elucidating this concept:

> validPortWgt <- function(object){

+ if(object@LongOnly){

+ if(any(object@Weights < 0)){

+ return("\nNegative weights for long-only.")

+ }

+ }

+ if(!object@Leveraged){

+ if(sum(abs(object@Weights)) > 1){

+ return("\nAbsolute sum of weights greater than one.")

+ }

+ }

+ TRUE + }

> setValidity("PortWgt", validPortWgt) Class "PortWgt" [in ".GlobalEnv"]

Slots:

Name: Weights Name Date Leveraged LongOnly

Class: numeric character character logical logical

This function returnsTRUEif the supplied information is valid and in accordance with the class specification, or an informative message otherwise:

> PortWgt(Weights = rep(-0.2, 5),

+ Name = "Equal Weighted", LongOnly = TRUE)

Error in validObject(.Object) : invalid class Negative weights for long-only.

In the above in-line statement the erroneous creation of aPortWgtobject was tried for a long-only portfolio, but with negative weights. An error message is returned

k k and the user is alerted that at least one weight is negative and hence in conflict with

the long-only characteristic. Similarly, in the following example the sum of weights is greater than 1 for a nonleveraged portfolio and hence the object is not created, but an informative error message as defined invalidPortWgt()is returned:

> PortWgt(Weights = rep(0.3, 5),

+ Name = "Equal Weighted", Leveraged = FALSE)

Error in validObject(.Object) : invalid class Absolute sum of weights greater than one.

So far, anS4class for portfolio weights,PortWgt, has been defined and a con- structor functionPortWgt()has been created along with a function for validating the user-supplied arguments. The rest of this section shows howS4methods can be defined. First, ashow()method for nicely displaying the portfolio weights is created by means ofsetMethod():

> setMethod("show", signature = "PortWgt", + function(object){

+ if(is.null(names(object@Weights))){

+ N <- length(object@Weights)

+ names(object@Weights) <- paste("Asset", 1:N)

+ }

+ cat(paste("Portfolio:", object@Name)) + cat("\n")

+ cat(paste("Long-Only:", object@LongOnly)) + cat("\n")

+ cat(paste("Leveraged:", object@Leveraged)) + cat("\n")

+ cat("Weights:\n") + print(object@Weights) + cat("\n")

+ }) [1] "show"

If the supplied weight vector has been passed to the creation of the object without names, a generic character vector is created first. In the rest of the body of theshow() method are calls to the functioncat()by which the content of thePortWgtobject will be displayed. The result will then look like this:

> P2

Portfolio: Equal Weighted Long-Only: TRUE

Leveraged: FALSE Weights:

Asset 1 Asset 2 Asset 3 Asset 4 Asset 5

0.2 0.2 0.2 0.2 0.2

k k It might make sense to define asummary()method for producing descriptive

statistics of the weight vector, which is accomplished by:

> setMethod("summary", "PortWgt", function(object, ...){

+ summary(object@Weights, ...) + })

[1] "summary"

> summary(P2)

Min. 1st Qu. Median Mean 3rd Qu. Max.

0.2 0.2 0.2 0.2 0.2 0.2

In this method definition the already existingsummary()method for objects of classnumericis directly applied to the slotWeights. Similarly, alength() method can be defined, which returns the count of assets as the length of this vector:

> setMethod("length", "PortWgt", function(x)

+ length(x@Weights)

+ )

[1] "length"

> length(P2) [1] 5

The reader might wonder why, in the first instance, the function’s definition is in terms offunction(object, ...)and in the secondfunction(x)only.

The reason lies in the differing specifications of the “generic” function. This spec- ification is displayed by invoking getMethod("foo") for method foo. Inci- dentally, a skeleton of a method definition for a particular classbaris created by method.skeleton("foo", "bar").

The next in-line example shows the creation of a generic functionweights() and an associated method for objects of classPortWgt. First, the generic function is defined without a default method and the method definition forPortWgtobjects follows next:

> setGeneric("weights", function(object) + standardGeneric("weights")

+ )

[1] "weights"

> setMethod("weights", "PortWgt", function(object)

+ object@Weights

+ )

[1] "weights"

> weights(P2)

[1] 0.2 0.2 0.2 0.2 0.2

It would be handy if this method could also be used for assigning new values to the slotWeights. For this, one proceeds likewise by defining:

> setGeneric("weights<-", function(x, ...,value) + standardGeneric("weights<-")

+ )

k k

[1] "weights<-"

> setReplaceMethod("weights", "PortWgt",

+ function(x, ..., value){

+ x@Weights <- value

+ x

+ })

[1] "weights<-"

> weights(P2) <- rep(0.25, 4)

> P2

Portfolio: Equal Weighted Long-Only: TRUE

Leveraged: FALSE Weights:

Asset 1 Asset 2 Asset 3 Asset 4

0.25 0.25 0.25 0.25

This time, because weights()is used as a replacement method, the function setReplaceMethod()has been invoked in its definition.

A final example shows how acoerce()method can be created by utilizing the setAs()function of themethodspackage:

> setAs(from = "PortWgt", to = "data.frame", function(from){

+ anames <- names(from@Weights) + if(is.null(anames)){

+ N <- length(from)

+ anames <- paste("Asset", 1:N)

+ }

+ ans <- data.frame(from@Date, t(weights(from))) + colnames(ans) <- c("Date", anames)

+ ans

+ })

> as(P2, "data.frame")

Date Asset 1 Asset 2 Asset 3 Asset 4

1 2015-10-09 0.25 0.25 0.25 0.25

In this call an object of classPortWgtis coerced into adata.frameobject by combining the date stamp and the portfolio weight vector. In this definition the previously definedlength()andweights()methods have been used. Note how this coercing method is invoked: the target class is included as a character string in the call toas(). This scheme is different than theS3-style coercing methods, such as as.data.frame(). Of course, this old-style method can also be defined for objects of classPortWgt, but this is left as an exercise for the reader.

The concept of a reference class is very different from theS3andS4paradigms.

The latter are best described as flavors of a functional object-oriented program- ming implementation, whereas a reference class is an instance of an encapsulated object-oriented programming style. In other words, forS3andS4classes, methods belong to functions, but are members for reference class objects. Furthermore,RC objects are mutable such that the ordinary R-like behavior of “copy-on-modify,”

that is, a copy of the local reference is enforced when a computation might alter a nonlocal reference, does not apply. As such,RCbehaves more like object-oriented

k k programming paradigms as encountered in languages such as Python, Java, and/or

C++. This behavior is accomplished by embeddingRCobjects in anenvironment slot of anS4class.

In the following in-line statements the classPortWgtis reengineered as reference classPortWgtRC:

> PortWgtRC <- setRefClass("PortWgtRC",

+ fields = list(

+ Weights = "numeric",

+ Name = "character",

+ Date = "character",

+ Leveraged = "logical",

+ LongOnly = "logical"))

The call tosetRefClass()is akin to the functionsetClass()introduced above for defining S4classes. In aRCobject a “field” is similar to a “slot” inS4 classes. New object instances ofPortWgtRCare created by invoking the$new() method onRCinstances:

> P3 <- PortWgtRC$new()

> P3

Reference class object of class "PortWgtRC"

Field "Weights":

numeric(0) Field "Name":

character(0) Field "Date":

character(0) Field "Leveraged":

logical(0) Field "LongOnly":

logical(0)

Because no$initialize()method has been defined, all fields are prefilled with their default (“empty”) values. Assignment of field values can either be accomplished in the call to the $new() method or in statements of the form foo$fieldname:

> P3$Weights <- rep(0.2, 5)

> P3$Name <- "Equal Weighted"

> P3$Date <- "2001-03-31"

> P3$LongOnly <- TRUE

> P3$Leveraged <- FALSE

The mutability ofRCobjects is illustrated by trying to “copy” an object and chang- ing the content of one of its fields:

> P4RC <- P3

> P4RC$LongOnly <- FALSE

> P3$LongOnly [1] FALSE

k k This behavior is probably not expected by an unwary user and in contrast to the

S4class implementation:

> P4S4 <- P1

> P4S4@LongOnly <- FALSE

> P1@LongOnly [1] TRUE

All reference classes inherit from the classenvRefClasswhich provides some useful methods, such as$copy(). Hence, if one would like to copy a reference class object, one should pursue the following route:

> P3$LongOnly <- TRUE

> PortWgtRC$methods()

[1] "callSuper" "copy" "export"

[4] "field" "getClass" "getRefClass"

[7] "import" "initFields" ".objectPackage"

[10] ".objectParent" "show" "trace"

[13] "untrace" "usingMethods"

> P4RC <- P3$copy()

> P4RC$LongOnly <- FALSE

> P3$LongOnly [1] TRUE

Methods for a reference class can either be defined within the call tosetRef- Class()as a named listmethodsor through the inherited$methods()creator, as in the following example in which the$show()method is redefined:

> PortWgtRC$methods(show = function(){

+ if(is.null(names(Weights))){

+ N <- length(Weights)

+ names(Weights) <<- paste("Asset", 1:N)

+ }

+ cat(paste("Portfolio:", Name)) + cat("\n")

+ cat(paste("Long-Only:", LongOnly)) + cat("\n")

+ cat(paste("Leveraged:", Leveraged)) + cat("\n")

+ cat("Weights:\n") + print(Weights) + cat("\n") + })

> P4 <- PortWgtRC$new(Weights = rep(0.2, 5),

+ Name = "Equal Weighted",

+ Date = "2001-03-31",

+ LongOnly = TRUE,

+ Leveraged = FALSE)

> P4

Portfolio: Equal Weighted Long-Only: TRUE

Leveraged: FALSE

k k

Weights:

Asset 1 Asset 2 Asset 3 Asset 4 Asset 5

0.2 0.2 0.2 0.2 0.2

Two points contained in the above method definition are noteworthy. First, in con- trast to the functional OO style ofS4methods, members of a reference class object can be accessed directly in the function body of the method definition, for example, Weightsinstead ofobjectWeights. Second, members can only be altered by using the nonlocal assignment operator<<-.

This has been a very concise introduction to the available OO styles inR. First-time Rusers are likely to be irritated by these three complementary class/method schemes, but might return to the literature and manual references provided for an in-depth dis- cussion. As a novice Ruser progresses on the learning curve, s/he will probably appreciate the ability to choose from three distinct class/method incarnations: one informal functional OO style (S3), a more elaborate implementation (S4), and an encapsulated one (RC). Each of these facilities has its strength and weakness. For instance, theS4class/method scheme can be utilized for the formulation of portfo- lio problems and finding an optimal solution; reference class objects might come in handy for back-testing portfolio strategies and thereby exploiting the mutability of the portfolio weights through time; and, last but not least, theS3scheme can be fruitfully exploited for fast prototyping ofRcode and/or statistical model/distribution fitting.

Một phần của tài liệu Financial risk modelling and portfolio optimization with r second edition (Trang 27 - 37)

Tải bản đầy đủ (PDF)

(436 trang)