summaryrefslogtreecommitdiffstats
path: root/R
diff options
context:
space:
mode:
authorGuillaume Horel <guillaume.horel@serenitascapital.com>2014-06-27 16:49:22 -0400
committerGuillaume Horel <guillaume.horel@serenitascapital.com>2014-06-27 16:49:22 -0400
commit6b572b022895a93f8bd648b0f25d45ac419ea616 (patch)
tree9d7d3d1746af3d4fabdf0ccbd62bbfbe79299b50 /R
parent2776a1ad9bd9fd70c5cc098516ed9f3377d257e3 (diff)
downloadlossdistrib-6b572b022895a93f8bd648b0f25d45ac419ea616.tar.gz
simplify code
Diffstat (limited to 'R')
-rw-r--r--R/tranche_functions.R87
1 files changed, 35 insertions, 52 deletions
diff --git a/R/tranche_functions.R b/R/tranche_functions.R
index 121df6a..469d68f 100644
--- a/R/tranche_functions.R
+++ b/R/tranche_functions.R
@@ -657,45 +657,51 @@ BClossdistC <- function(defaultprob, issuerweights, recov, rho, Z, w,
return(list(L=r$L,R=r$R))
}
-BCtranche.pv <- function(index, K1, K2, rho1, rho2,
- Z, w, N=length(index$issuerweights)+1, protection=FALSE){
+BCtranche.legs <- function(index, K, rho){
+ ## computes the protection leg and couponleg of a 0-K tranche
+ dist <- BClossdistC(index$defaultprob, index$issuerweights, index$recov, rho, index$Z, index$w, index$N)
+ return(list(cl=tranche.cl(dist$L, dist$R, index$cs, 0, K), pl=tranche.pl(dist$L, index$cs, 0, K)))
+}
+
+BCtranche.pv <- function(index, protection=FALSE){
## computes the protection leg, couponleg, and bond price of a tranche
## in the base correlation setting
- if(K1==0){
- if(rho1!=0){
- stop("equity tranche must have 0 lower correlation")
- }
- }
- dK <- K2 - K1
- dist2 <- BClossdistC(index$defaultprob, index$issuerweights, index$recov, rho2, Z, w, N)
- if(rho1!=0){
- dist1 <- BClossdistC(index$defaultprob, index$issuerweights, index$recov, rho1, Z, w, N)
- }
- cl2 <- tranche.cl(dist2$L, dist2$R, index$cs, 0, K2)
- cl1 <- tranche.cl(dist1$L, dist1$R, index$cs, 0, K1)
- pl2 <- tranche.pl(dist2$L, index$cs, 0, K2)
- pl1 <- tranche.pl(dist1$L, index$cs, 0, K1)
+ pl <- rep(0, length(index$rho)-1)
+ cl <- rep(0, length(index$rho)-1)
+ for(i in 2:(length(index$rho)-1)){
+ temp <- BCtranche.legs(index, index$K[i], index$rho[i])
+ pl[i] <- temp$pl
+ cl[i] <- temp$cl
+ }
+ dK <- diff(index$K)
+ plvec <- diff(pl)/dK[-length(dK)]
+ clvec <- diff(cl)/dK[-length(dK)]*index$tranche.running[-length(index$tranche.running)]
+ ## compute the supersenior as the left over
+ temp <- indexpv(index, tradedate = tradedate, clean = FALSE)
+ indexpl <- temp$pl
+ indexcl <- temp$cl/index$quotes$spread
+ plvec <- c(plvec, -(indexpl+pl[4])/dK[length(dK)])
+ clvec <- c(clvec, (indexcl-cl[4])*index$tranche.running[length(index$tranche.running)]/dK[length(dK)])
if(protection){
- bp <- (pl1-pl2+cl1-cl2)/dK
+ bp <- -plvec-clvec
}else{
- bp <- 100*(1-(pl2-pl1+cl2-cl1)/dK)
+ bp <- 1+plvec+clvec
}
- return(list(pl=(pl2-pl1)/dK, cl=(cl2-cl1)/dK, bp=bp))
+ return(list(pl=plvec, cl=clvec, 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)
+ elshort <- EL(index, shortened)
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))
+ return(c(0, rhofun(K)))
}
-BCtranche.delta <- function(index, Z, w, N=length(index$portolio)+1, tradedate = Sys.Date()){
+BCtranche.delta <- function(index, tradedate = Sys.Date()){
## computes the tranche delta (on current notional) by doing a proportional
## blip of all the curves
## if K2==1, then computes the delta using the lower attachment only
@@ -720,39 +726,16 @@ 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$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))
- for(i in 1:(length(index$rho)-2)){
- dist.list <- list()
- for(j in seq_along(index.list)){
- dist.list[[j]] <- BClossdistC(index.list[[j]]$defaultprob,
- index$issuerweights, index$recov, index$rho[i+1], Z, w, N)
- }
- for(j in seq_along(dist.list)){
- #shock all the coupon and protection legs
- cl[i,j] <- tranche.cl(dist.list[[j]]$L, dist.list[[j]]$R, index$cs, 0, index$K[i+1])
- pl[i,j] <- tranche.pl(dist.list[[j]]$L, index$cs, 0, index$K[i+1])
- }
+ bp <- matrix(0, length(index$K)-1, 4)
+ for(j in seq_along(index.list)){
+ temp <- BCtranche.pv(index.list[[j]])
+ bp[,j] <- temp$bp
}
- bp[1,] <- (pl[1,]+cl[1,]*index$tranche.running[1])
- for(i in 2:(nrow(cl))){
- bp[i,] <- pl[i,]-pl[i-1,]+(cl[i,]-cl[i-1,])*index$tranche.running[i]
- }
- bp[nrow(bp),] <- pl[nrow(pl),]+cl[nrow(cl),]*index$tranche.running[length(index$tranche.running)]
- dPVtranche <- (bp[-nrow(bp),2]-bp[-nrow(bp),3])/diff(index$K[-length(index$K)])
- dPVtranche2 <- (bp[-nrow(bp),4] - bp[-nrow(bp),1])/diff(index$K[-length(index$K)])
+ dPVtranche <- bp[,2]-bp[,3]
+ dPVtranche2 <- bp[,4] - bp[,1]
deltas <- dPVtranche/dPVindex
deltasplus <- dPVtranche2/dPVindex2
- ##might need to check that in case of non 1 factor
- deltas <- c(deltas,
- (1-(bp[nrow(bp),2]-bp[nrow(bp),3])/dPVindex)/(1-index$K[length(index$K)-1]))
- ##might need to check that in case of non 1 factor
- deltasplus <- c(deltasplus,
- (1-(bp[nrow(bp),4]-bp[nrow(bp),1])/dPVindex2)/(1-index$K[length(index$K)-1]))
-
gammas <- (deltasplus-deltas)/dPVindex1/100
return( list(deltas=deltas, gammas=gammas) )