summaryrefslogtreecommitdiffstats
path: root/R
diff options
context:
space:
mode:
authorGuillaume Horel <guillaume.horel@serenitascapital.com>2014-06-25 17:34:36 -0400
committerGuillaume Horel <guillaume.horel@serenitascapital.com>2014-06-25 17:34:36 -0400
commit2776a1ad9bd9fd70c5cc098516ed9f3377d257e3 (patch)
treeebbcdc57ab9d3ea76cad9d529de0a923ada7f40a /R
parent290e3cc11ee6d529c7f862ec46861f4ac95254e7 (diff)
downloadlossdistrib-2776a1ad9bd9fd70c5cc098516ed9f3377d257e3.tar.gz
add function to theta adjust the skew
Diffstat (limited to 'R')
-rw-r--r--R/tranche_functions.R25
1 files changed, 19 insertions, 6 deletions
diff --git a/R/tranche_functions.R b/R/tranche_functions.R
index ce08288..121df6a 100644
--- a/R/tranche_functions.R
+++ b/R/tranche_functions.R
@@ -684,6 +684,17 @@ BCtranche.pv <- function(index, K1, K2, rho1, rho2,
return(list(pl=(pl2-pl1)/dK, cl=(cl2-cl1)/dK, bp=bp))
}
+
+theta.adjust.skew <- function(index, shortened=4){
+ #ajust the correlation skew by doing ATM mapping on the expected loss
+ el <- EL(index)
+ elshort <- EL(index, shortened=4)
+ K <- index$K[-c(1,length(index$K))]
+ rhofun <- splinefun(K, index$rho[-c(1, length(index$rho))], "natural")
+ K <- el/elshort*K
+ return(rhofun(K))
+ }
+
BCtranche.delta <- function(index, Z, w, N=length(index$portolio)+1, tradedate = Sys.Date()){
## computes the tranche delta (on current notional) by doing a proportional
## blip of all the curves
@@ -709,7 +720,7 @@ BCtranche.delta <- function(index, Z, w, N=length(index$portolio)+1, tradedate =
dPVindex1 <- indexpv(index.list[[2]], tradedate = tradedate, clean = FALSE)$bp-
indexpv(index, tradedate = tradedate, clean = FALSE)$bp
- index$cs$coupons <- index$cs$coupons/index$spreadref
+ index$cs$coupons <- index$cs$coupons/index$quotes$spread
cl <- matrix(0, length(index$rho)-2, length(index.list))
pl <- matrix(0, length(index$rho)-2, length(index.list))
bp <- matrix(0, length(index$rho)-1, length(index.list))
@@ -747,16 +758,18 @@ BCtranche.delta <- function(index, Z, w, N=length(index$portolio)+1, tradedate =
return( list(deltas=deltas, gammas=gammas) )
}
-EL <- function(index, discounted=TRUE){
+EL <- function(index, discounted=TRUE, shortened=0){
## computes the expected loss of a portfolio (time discounted if discounted is TRUE)
## given the default curves and recovery
## should be very close to the protection leg of the portfolio of cds
## index should be a list with issuerweights, recov, defaultprob and cs parameters
- ELvec <- as.numeric(crossprod(index$issuerweights * (1-index$recov), index$defaultprob))
+ ## shortened: number of quarters to shorten the maturity by
+ Ncol <- ncol(index$defaultprob)-shortened
+ ELvec <- as.numeric(crossprod(index$issuerweights * (1-index$recov), index$defaultprob[,1:Ncol]))
if(!discounted){
return( diff(c(0, ELvec)) )
}else{
- return( sum(index$cs$df*diff(c(0, ELvec))) )
+ return( sum(index$cs$df[1:Ncol]*diff(c(0, ELvec))) )
}
}
@@ -778,10 +791,10 @@ ELtrunc <- function(index, K, rho, Z, w, Ngrid){
BCstrikes <- function(defaultprob, issuerweights, recov, cs, K, rho, Z, w, N=101) {
## computes the strikes as a percentage of expected loss
## Kmodified is the current attachment points (adjusted for losses)
- el <- EL(defaultprob, issuerweights, recov, cs)
+ el <- EL(index)
ELvec <- c()
for(i in 2:length(K)){
- ELvec <- c(ELvec, ELtrunc(defaultprob, issuerweights, recov, cs, K[i], rho[i], Z, w, N))
+ ELvec <- c(ELvec, ELtrunc(index, K[i], rho[i], Z, w, N))
}
return( ELvec/el )
}