[R-SIG-Finance] coskewness, cokurtosis, and higher beta co-moments of the return distribution (implemented)

Brian G. Peterson brian at braverock.com
Thu Aug 10 14:05:43 CEST 2006


As I discussed in my posts on Modified Cornish-Fisher VaR, many papers in 
the literature use higher moments of the return vector of an instrument 
to aid in the analysis of the returns for non-normal distributions.  The 
R 'stats' package contains functions for mean, variance, and covariance. 
RMetrics by Diethelm Wuertz contains functions for skewness and kurtosis, 
but does not contain any of the higher co-moments of the return 
distribution.

I've attached a .R file that contains functions for coskewness, 
cokurtosis, betacoskewness (or systematic skewness), betacokurtosis (or 
systematic kurtosis), and betacovariance (or systematic beta).

The use of the higher co-moments of the return distribution function may 
aid practitioners in analyzing the extreme downside risks and 
diversification potential of non-normally distributed assets.

My earlier posts on Modified Cornish-Fisher VaR may be found here:
    http://article.gmane.org/gmane.comp.lang.r.r-metrics/855

The current and all future versions of the attached file may be found 
here:
http://braverock.com/brian/R/extra_moments.R

I hope you find it useful.  Any comments, criticisms, or suggestions for 
improvement are gladly accepted.

Regards,

   - Brian

-------------- next part --------------
# This library is free software; you can redistribute it and/or
# modify it under the terms of the GNU General Public License
# as published by the Free Software Foundation; either
# version 2 of the License, or (at your option) any later version.
#
# This library is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU Library General Public License for more details.
#
# You should have received a copy of the GNU General
# Public License along with this library; if not,
# go here: http://www.gnu.org/licenses/gpl.html
# or write to the
# Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston,
# MA  02111-1307  USA

# Copyright 2006 Brian G. Peterson for this R-port


################################################################################
# FUNCTIONS:
# ThirdMoment
# FourthMoment
# modifiedVaR
# CoSkewness
# CoKurtosis
# BetaCoVariance
# BetaCoV (wrapper for BetaCoVariance)
# SystematicBeta (wrapper for BetaCoVariance)
# BetaCoSkewness
# BetaCoS (wrapper for BetaCoSkewness)
# SystematicSkewness (wrapper for BetaCoSkewness)
# BetaCoKurtosis
# BetaCoK (wrapper for BetaCoKurtosis)
# SystematicKurtosis (wrapper for BetaCoKurtosis)
# modifiedVaR
#
################################################################################


################################################################################
# The following functions are intended to replicate calculations for
# taking higher moments of hedge fund returns into account in analyzing
# particular investments.  Most of the formulae are taken from various EDHEC
# research papers.

# All returns are assumed to be on a monthly scale!
# The argument r is the monthly return time series !

# @todo add modifiers for Risk-free rate, presumed to be zero in these functions

# @todo add ability to account for multidimensionality of
#       systematic beta, systematic skewness, and systematic kurtosis

# ------------------------------------------------------------------------------
std =
function(r)
{   # A function implemented by Diethelm Wuertz
    # NOTE: std function is listed in the doc for fBasics, but not implemented
    # Standard deviation of Monthly Returns:
    result = sqrt(var(r))

    # Return Value:
    result
}

library("fBasics")

# ------------------------------------------------------------------------------
ThirdMoment=
function(Ri,na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # The third mathematical moment of the return function.
    # Favre and Renaldo use this as separate from skewness in developing a
    # four-moment CAPM model
    #
    # as defined in:
    # Favre, L. and Renaldo, A., October 2003
    # How to Price Hedge Funds: From Two- to Four-Moment CAPM
    # UBS and Edhec Business School

    # Setup

    Ri = as.vector(Ri)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
    }

    # FUNCTION:

    S = (mean((Ri-mean(Ri)^3)))^(1/3)

    result = S

    # Return Value:
    result
}

# ------------------------------------------------------------------------------
FourthMoment=
function(Ri,na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # The fourth mathematical moment of the return function.
    # Favre and Renaldo use this as separate from kurtosis in developing a
    # four-moment CAPM model
    #
    # as defined in:
    # Favre, L. and Renaldo, A., October 2003
    # How to Price Hedge Funds: From Two- to Four-Moment CAPM
    # UBS and Edhec Business School

    # Setup

    Ri = as.vector(Ri)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
    }

    # FUNCTION:

    K = (mean((Ri-mean(Ri)^4)))^(1/4)

    result = K
    # Return Value:
    result
}

# ------------------------------------------------------------------------------
CoSkewness =
function(Ri, Ra, na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # CoSkewness is the product of the third higher moments of two assets,
    # as defined in
    # Martellini L. and Ziemann V., 2005,
    # Marginal Impacts on Portfolio Distributions,
    # Working Paper, Edhec Risk and Asset Management Research Centre
    # and in:
    # Martellini L., Vaissie M., Ziemann V., October 2005,
    # Investing in Hedge Funds:
    #   Adding Value through Active Style Allocation Decisions
    # Edhec Risk and Asset Management Research Centre

    # Ri = return vector of initial portfolio
    # Ra = return vector of asset being considered for addition to portfolio

    # Setup

    Ri = as.vector(Ri)
    Ra = as.vector(Ra)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
        Ra <- Ra[!is.na(Ra)]
    }

    # FUNCTION:

    # CoSkewness of two assets
    CoS = mean((Ri - mean(Ri))*((Ra-mean(Ra))^2))

    result = CoS

    # Return Value:
    result
}

# ------------------------------------------------------------------------------
CoKurtosis =
function(Ri, Ra, na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # CoKurtosis is the product of the fourth higher moments of two assets,
    # as defined in
    # Martellini L. and Ziemann V., 2005,
    # Marginal Impacts on Portfolio Distributions,
    # Working Paper, Edhec Risk and Asset Management Research Centre
    # and in:
    # Martellini L., Vaissie M., Ziemann V., October 2005,
    # Investing in Hedge Funds:
    #   Adding Value through Active Style Allocation Decisions
    # Edhec Risk and Asset Management Research Centre

    # Ri = return vector of initial portfolio
    # Ra = return vector of asset being considered for addition to portfolio

    # Setup

    Ri = as.vector(Ri)
    Ra = as.vector(Ra)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
        Ra <- Ra[!is.na(Ra)]
    }

    # FUNCTION:

    # CoKurtosis of two assets
    CoK = mean((Ri - mean(Ri))*((Ra-mean(Ra))^3))

    result = CoK

    # Return Value:
    result
}

# ------------------------------------------------------------------------------
BetaCoVariance =
function(Ri, Ra, na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # Beta covariance is the beta of an asset to the variance and covariance
    # of an initial portfolio.  Used to determine diversification potential.
    # also called "systematic beta" by several papers
    #
    # as defined in
    # Favre, L. and Renaldo, A., October 2003
    # How to Price Hedge Funds: From Two- to Four-Moment CAPM
    # UBS and Edhec Business School
    # Equation [5] p. 10

    # Ri = return vector of initial portfolio
    # Ra = return vector of asset being considered for addition to portfolio

    # Setup

    Ri = as.vector(Ri)
    Ra = as.vector(Ra)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
        Ra <- Ra[!is.na(Ra)]
    }

    # FUNCTION:

    # CovarianceBeta of two assets
    covB = cov(Ra,Ri)/var(Ri)

    result = covB

    # Return Value:
    result
}

BetaCoV =
function(Ri, Ra, na.rm=FALSE)
{
    # wrapper function with a shorter name
    result = BetaCoVariance(Ri, Ra, na.rm)
    # Return Value:
    result
}

SystematicBeta =
function(Ri, Ra, na.rm=FALSE)
{
    # wrapper function with a shorter name
    result = BetaCoVariance(Ri, Ra, na.rm)
    # Return Value:
    result
}

# ------------------------------------------------------------------------------
BetaCoSkewness =
function(Ri, Ra, na.rm=FALSE)
{ # @author Brian G. Peterson

    # Description:
    # Beta CoSkewness is the beta of an asset to the skewness
    # of an initial portfolio.  Used to determine diversification potential.
    # also called "systematic skewness" or "systematic co-skewness"
    # by several papers.
    # as defined in
    # Favre, L. and Renaldo, A., October 2003
    # How to Price Hedge Funds: From Two- to Four-Moment CAPM
    # UBS and Edhec Business School
    # Equation [5] p. 10

    # Ri = return vector of initial portfolio
    # Ra = return vector of asset being considered for addition to portfolio

    # Setup

    Ri = as.vector(Ri)
    Ra = as.vector(Ra)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
        Ra <- Ra[!is.na(Ra)]
    }

    # FUNCTION:

    # systematic skewness of two assets
    skB = CoSkewness(Ra,Ri)/(mean(Ri-mean(Ri))^3)

    result = skB

    # Return Value:
    result
}

BetaCoS =
function(Ri, Ra, na.rm=FALSE)
{
    # wrapper function with a shorter name
    result = BetaCoSkewness(Ri, Ra, na.rm)
    # Return Value:
    result
}

SystematicSkewness =
function(Ri, Ra, na.rm=FALSE)
{
    # wrapper function with a shorter name
    result = BetaCoSkewness(Ri, Ra, na.rm)
    # Return Value:
    result
}

# ------------------------------------------------------------------------------
BetaCoKurtosis =
function( Ri, Ra, na.rm=FALSE, method=c("moment", "excess", "fisher") )
{ # @author Brian G. Peterson

    # Description:
    # Beta CoKurtosis is the beta of an asset to the kurtosis
    # of an initial portfolio.  Used to determine diversification potential.
    # Also called "systematic kurtosis" or "systematic cokurtosis" by several papers.
    #
    # as defined in
    # Martellini L., Vaissie M., Ziemann V., October 2005,
    # Investing in Hedge Funds:
    #   Adding Value through Active Style Allocation Decisions
    # Edhec Risk and Asset Management Research Centre


    # Ri = return vector of initial portfolio
    # Ra = return vector of asset being considered for addition to portfolio

    # Setup

    Ri = as.vector(Ri)
    Ra = as.vector(Ra)

    if(na.rm) {
        Ri <- Ri[!is.na(Ri)]
        Ra <- Ra[!is.na(Ra)]
    }

    # FUNCTION:

    # Beta CoKurtosis of two assets
    ktB = CoKurtosis(Ra,Ri)/kurtosis(Ri, na.rm ,method ) #method = c("excess", "moment", "fisher")

    result = ktB

    # Return Value:
    result
}

BetaCoK =
function( Ri, Ra, na.rm=FALSE, method=c("moment", "excess", "fisher") )
{
    # wrapper function with a shorter name
    result = BetaCoKurtosis(Ri, Ra, na.rm, method)
    # Return Value:
    result
}

SystematicKurtosis =
function( Ri, Ra, na.rm=FALSE, method=c("moment", "excess", "fisher") )
{
    # wrapper function with a shorter name
    result = BetaCoKurtosis(Ri, Ra, na.rm, method)
    # Return Value:
    result
}

# ------------------------------------------------------------------------------
modifiedVaR =
function(r, modified = TRUE, p=0.99, column=1)
{   # @author Diethelm Wuertz (original prototype fn)
    # @author Brian G. Peterson (completed/debugged fn)

    # Description:

    # The limitations of mean Value-at-Risk are well covered in the literature.
    # Laurent Favre and Jose-Antonio Galeano published a paper in the
    # Fall 2002, volume 5 of the Journal of Alternative Investment,
    # "Mean-Modified Value-at-Risk optimization With Hedge Funds",
    # that proposed a modified VaR calculation that takes the higher moments
    # of non-normal distributions (skewness, kurtosis) into account, and
    # collapses to standard mean-VaR if the return stream follows a
    # standard distribution.
    # This measure is now widely cited and used in the literature,
    # and is usually referred to as "Modified VaR" or "Modified Cornish-Fisher VaR"

    # Diethelm Wuertz's original function was called monthlyVaR, but did not
    # contain the required modifications to get to a monthly or an annualized number.
    # I have converted it to modifiedVaR, and made the assumption of p=0.99, with an option for p=0.95 and
    # a collapse to normal mean VaR.

    # FUNCTION:

    # NOTE: see the data type conditionals in 'cov' and replicate here
    if (class(r) == "matrix") {
        r = r[, column]
        warning("Column ", column, colnames(r)[,column], " of matrix used")
    }
    if (class(r) == "data.frame") {
        r = r[, column]
        warning("Column ", column, colnames(r)[,column], " of data.frame used")
    }
    if (class(r) == "timeSeries") {
        r = r at Data[, column]
        warning("Column ", column, colnames(r)[,column], " of timeSeries used")
    }
    if (!is.numeric(r)) stop("The selected column is not numeric")
    r = as.vector(r)

    if ( p == 0.95 ) {
        zc = -1.96 #95% probability
    }
    if ( p == 0.99 ) {
        zc = -2.33 #99% probability
    }
    #} else {
    #    #some function here to compute zc with arbitrary p
    #}

    if (modified) {
        s = colSkewness(r) #use regular skewness and kurtosis fn if data.frame is converted to matrix?
        k = colKurtosis(r) #to compute excess kurtosis
        Zcf = zc + (((zc^2-1)*s)/6) + (((zc^3-3*zc)*k)/24) + (((2*zc^3)-(5*zc)*s^2)/36)
        result = mean(r) - (Zcf * sqrt(var(r)))
    } else {
        # should probably add risk-free-rate skew here?
        result = mean(r) - (zc * sqrt(var(r)))
    }

    # Return Value:
    result
}

################################################################################


More information about the R-SIG-Finance mailing list