diff options
| -rw-r--r-- | R/calibrate_tranches_BC.R | 8 | ||||
| -rw-r--r-- | R/calibration.R | 17 | ||||
| -rw-r--r-- | R/cds_functions_generic.R | 55 |
3 files changed, 53 insertions, 27 deletions
diff --git a/R/calibrate_tranches_BC.R b/R/calibrate_tranches_BC.R index 5b9d69d0..b002e515 100644 --- a/R/calibrate_tranches_BC.R +++ b/R/calibrate_tranches_BC.R @@ -16,7 +16,7 @@ n.int <- 250 attach(GHquad(n.int))
Ngrid <- 201
-alldates <- seq(as.Date("2014-01-01"), as.Date("2014-01-05"), by="1 day")
+alldates <- seq(as.Date("2014-03-04"), as.Date("2014-01-05"), by="1 day")
aux <- function(rho, index, N, K, quote){
temp <- BClossdistC(index$defaultprob, index$issuerweights, index$recov, rho, Z, w, N)
@@ -24,7 +24,7 @@ aux <- function(rho, index, N, K, quote){ }
bus.dates <- as.Date(names(which(isBusinessDay(calendar="UnitedStates/GovernmentBond", alldates))))
-for(index.name in c("hy19", "hy21"){
+for(index.name in c("hy19")){
rhomat <- c()
deltasmat <- c()
gammasmat <- c()
@@ -43,10 +43,10 @@ for(index.name in c("hy19", "hy21"){ index$cs$coupons <- dT*index$tranche.running[j]
## we compute the 0-index$K[j+1] equivalent quote using the coupon of the jth quote
if(j==1){
- q <- index$quotes[j]*index$K[j+1]
+ q <- index$tranche.quotes[j]*index$K[j+1]
}else{
q <- BCtranche.pv(index, 0, index$K[j], 0, rhovec[j], Z, w, Ngrid, TRUE)$bp * index$K[j]+
- index$quotes[j]*(index$K[j+1]-index$K[j])
+ index$tranche.quotes[j]*(index$K[j+1]-index$K[j])
}
rho <- optimize(aux, interval=c(0,1), index=index, N=Ngrid, K=index$K[j+1], quote=q)$minimum
rhovec <- c(rhovec, rho)
diff --git a/R/calibration.R b/R/calibration.R index 9ef99a83..7394dbec 100644 --- a/R/calibration.R +++ b/R/calibration.R @@ -22,7 +22,7 @@ get.cdsSchedule <- function(tradedate, indexmaturity){ for(tenor in paste0(c(1:5, 7,10), "y")){ newdate <- cdsMaturity(tenor, date=tradedate) cdsdates <- c(cdsdates, newdate) - if(newdate>indexmaturity){ + if(newdate>=indexmaturity){ break } } @@ -51,18 +51,19 @@ set.singlenamesdata <- function(index, tradedate){ set.tranchedata <- function(index, tradedate){ temp <- get.tranchequotes(index$name, index$tenor, tradedate) - index$spreadref <- temp$indexrefspread[1]*1e-4 + index$quotes <- data.frame(spread=temp$indexrefspread[1]*1e-4, maturity=index$maturity) if(index$name=="ig19" || index$name=="ig21"){ - index$spreadref <- 0.01 + index$quotes$spread <- 0.01 } - index$cs <- couponSchedule(IMMDate(tradedate), index$maturity,"Q", "FIXED", index$spreadref, + index$cs <- couponSchedule(IMMDate(tradedate, noadj=TRUE), index$maturity,"Q", "FIXED", + index$quotes$spread[1], 0, tradedate, IMMDate(tradedate, "prev")) if(!is.na(temp$indexrefprice[1])&&temp$indexrefprice[1]!=0){ - index$priceref <- temp$indexrefprice[1]/100 + index$quotes$price <- temp$indexrefprice[1]/100 }else{ sc <- new("flatcurve", h=temp$indexrefspread[1]*1e-4/(1-index$recovery)) index$priceref <- 1 + cdspv(index$cs, sc, index$recovery, tradedate)- - cdsAccrued(tradedate, index$spreadref) + cdsAccrued(tradedate, index$quotes$spread[1]) } index$portfolio <- tweakcurves(index, tradedate)$portfolio index$defaultprob <- 1 - SPmatrix(index$portfolio, length(index$cs$dates)) @@ -76,9 +77,9 @@ set.tranchedata <- function(index, tradedate){ index$tranche.running <- temp$trancherunning*1e-4 ## compute dirty protection price if(length(grep("hy", index$name, ignore.case=TRUE))>0){ - index$quotes <- 1-index$tranche.upf/100-cdsAccrued(tradedate, index$tranche.running) + index$tranche.quotes <- 1-index$tranche.upf/100-cdsAccrued(tradedate, index$tranche.running) }else{ - index$quotes <- index$tranche.upf/100+cdsAccrued(tradedate, index$tranche.running) + index$tranche.quotes <- index$tranche.upf/100+cdsAccrued(tradedate, index$tranche.running) } return( index ) } diff --git a/R/cds_functions_generic.R b/R/cds_functions_generic.R index 2f4fbf7a..f5afd0f5 100644 --- a/R/cds_functions_generic.R +++ b/R/cds_functions_generic.R @@ -524,13 +524,14 @@ bondhazardrate.shaped <- function(collateral, shape, R=0.4, alpha=0.25, beta=15, return( shapedtodpc(cs, sc, startdate) )
}
-tweakportfolio <- function(portfolio, epsilon, multiplicative=TRUE){
+tweakportfolio <- function(portfolio, epsilon, multiplicative=TRUE, forward.tweak=1){
## tweak a portfolio of creditcurves
## if multiplicative is TRUE apply a multiplicative tweak
## otherwise apply an additive one
if(multiplicative){
r <- lapply(portfolio, function(x) {
- x@curve@hazardrates <- x@curve@hazardrates * (1+epsilon)
+ x@curve@hazardrates[forward.tweak:length(x@curve@hazardrates)] <-
+ x@curve@hazardrates[forward.tweak:length(x@curve@hazardrates)] * (1+epsilon)
x
})
}else{
@@ -543,17 +544,24 @@ tweakportfolio <- function(portfolio, epsilon, multiplicative=TRUE){ return( r )
}
-indexpv <- function(index, epsilon=0, tradedate=Sys.Date(), clean=TRUE){
+indexpv <- function(index, epsilon=0, tradedate=Sys.Date(), clean=TRUE,
+ maturity=index$maturity, forward.tweak=1){
## computes the intrinsic price of a portfolio of cds
+ ## If maturity is provided, only computes the pv up to that point
+ ## (Say we compute the 3 year pv based on 5 year curves
+ ## forward.tweak only makes sense if epsilon is non zero
+ ## and will teak the curves starting from forward.index
if(epsilon!=0){
- portfolio <- tweakportfolio(index$portfolio, epsilon)
+ portfolio <- tweakportfolio(index$portfolio, epsilon, forward.tweak=forward.tweak)
}else{
portfolio <- index$portfolio
}
startdate <- tradedate + 1
- cl.list <- unlist(lapply(portfolio, function(x){couponleg(index$cs, x@curve, startdate)}))
- pl.list <- unlist(lapply(portfolio, function(x){defaultleg(index$cs, x@curve, x@recovery, startdate)}))
- accrued <- cdsAccrued(tradedate, index$spreadref)
+ cs <- index$cs[index$cs$dates<=maturity,]
+ cl.list <- unlist(lapply(portfolio, function(x){couponleg(cs, x@curve, startdate)}))
+ pl.list <- unlist(lapply(portfolio, function(x){defaultleg(cs, x@curve, x@recovery, startdate)}))
+ spread <- index$quotes$spread[index$quotes$maturity==maturity]
+ accrued <- cdsAccrued(tradedate, spread)
r <- list(cl = mean(cl.list) - accrued, pl = mean(pl.list), bp = 1+mean(cl.list-pl.list))
if(clean){
r$bp <- r$bp-accrued
@@ -561,13 +569,13 @@ indexpv <- function(index, epsilon=0, tradedate=Sys.Date(), clean=TRUE){ return(r)
}
-indexduration <- function(portfolio, index){
+indexduration <- function(index){
## compute the duration of a portfolio of survival curves
- durations <- unlist(lapply(portfolio, function(x){cdsduration(x@curve, index$maturity)}))
+ durations <- unlist(lapply(index$portfolio, function(x){cdsduration(x@curve, index$maturity)}))
return( mean(durations) )
}
-indexspread <- function(portfolio, index){
+indexspread <- function(index){
## computes the spread of a portfolio of survival curves
## S <- 0
## d <- rep(0, length(portfolio))
@@ -575,10 +583,19 @@ indexspread <- function(portfolio, index){ ## d[i] <- cdsduration(portfolio[[i]]@curve, index$maturity)
## S <- S + d[i] * cdsspread(portfolio[[i]]@curve, index$maturity, portfolio[[i]]@recovery)
## }
- S <- index$coupon-(indexpv(portfolio, index)$bp-1)/indexduration(portfolio, index)
+ S <- index$spreadref-(indexpv(index)$bp-1)/indexduration(index)
return(S)
}
+indextheta <- function(index, tradedate=Sys.Date()){
+ current.pv <- indexpv(index, tradedate=tradedate)$bp
+ newmaturity <- index$cs$dates[nrow(orig.cs)-4]
+ forward.pv <- indexpv(index, tradedate=tradedate, maturity=newmaturity)$bp
+ theta <- forward.pv-current.pv+index$spreadref
+ return( theta )
+}
+
+
portfoliospread <- function(portfolio, maturity){
## computes the spread of a portfolio defined by notionals and survivalcurves
## for a given maturity.
@@ -612,11 +629,19 @@ portfolioduration <- function(portfolio, maturity){ tweakcurves <- function(index, tradedate=Sys.Date()){
## computes the tweaking factor
- epsilon <- 0
- f <- function(epsilon, ...){
- abs(indexpv(index, epsilon, tradedate)$bp - index$priceref)
+ epsilon <- rep(0, nrow(index$quotes))
+ for(i in 1:nrow(index$quotes)){
+ if(i==1){
+ forward.tweak <- 1
+ }else{
+ forward.tweak <- which.min(index$cs$dates>index$quotes$maturity[i-1])
+ }
+ f <- function(epsilon, ...){
+ abs(indexpv(index, epsilon, tradedate, maturity=index$quotes$maturity[i],
+ forward.tweak=forward.tweak)$bp - index$quotes$price[i])
+ }
+ epsilon[i] <- optimize(f, c(-0.15, 0.15), index, tol=1e-6)$minimum
}
- epsilon <- optimize(f, c(-0.15, 0.15), index, tol=1e-6)$minimum
cat("tweak = ", epsilon, "\n")
return( list(portfolio=tweakportfolio(index$portfolio, epsilon), epsilon=epsilon) )
}
|
