diff options
Diffstat (limited to 'R')
| -rw-r--r-- | R/calibrate_tranches_BC.R | 89 | ||||
| -rw-r--r-- | R/creditIndex.R | 50 |
2 files changed, 63 insertions, 76 deletions
diff --git a/R/calibrate_tranches_BC.R b/R/calibrate_tranches_BC.R index 342daef7..562b1bb5 100644 --- a/R/calibrate_tranches_BC.R +++ b/R/calibrate_tranches_BC.R @@ -69,8 +69,10 @@ library(lossdistrib) for(i in seq_along(runs$name)){
index.name <- runs$name[i]
tenor <- runs$tenor[i]
+ filename <- file.path(root.dir,"Tranche_data","Runs",
+ paste(index.name,tenor,"csv",sep="."))
if(updateflag){##ghetto way of getting the last row of the file
- runfile <- read.csv(file.path(root.dir,"Tranche_data","Runs", paste(index.name,tenor,"csv",sep=".")))
+ runfile <- read.csv(filename)
begin.date <- as.Date(runfile[nrow(runfile),1])+1
}else{
begin.date <- switch(index.name,
@@ -88,86 +90,41 @@ for(i in seq_along(runs$name)){ if(index.name=="ig19"){
alldates <- alldates[alldates!=as.Date("2013-11-29")] ##people are lazy the day after Thanksgiving
}
- if(index.name=="hy21" & tenor =="3yr"){
- ##alldates <- alldates[alldates!=as.Date("2013-11-29")] ##people are lazy the day after Thanksgiving
- }
bus.dates <- as.Date(names(which(isBusinessDay(calendar="UnitedStates/GovernmentBond", alldates))))
- ##check if we have all the quotes and save them
- n.tranches <- 4
- if(index.name=="ig9"){
- n.tranches <- 6
- }
- quotes <- matrix(0, length(bus.dates), 2+2*n.tranches)
for(j in seq_along(bus.dates)){
tradedate <- bus.dates[j]
- temp <- get.tranchequotes(index.name, tenor, tradedate)
- quotes[j, 1] <- temp$indexrefprice[1]
- quotes[j, 2] <- temp$indexrefspread[1]
- quotes[j, 2+1:n.tranches] <- temp$trancheupfrontmid
- quotes[j, 2+n.tranches+1:n.tranches] <- temp$tranchedelta
- }
-
- tranche.names <- paste(temp$attach, temp$detach, sep="-")
- colnames(quotes) <- c("indexprice", "indexref",paste(tranche.names, "Upfront"),
- paste(tranche.names, "Dealer Delta"))
- Attach <- temp$detach
- ##preallocate all the risk matrices
- indexEL <- rep(0, length(bus.dates))
- indexTheta <- rep(0, length(bus.dates))
- indexBasis <- rep(0, length(bus.dates))
- deltas <- matrix(0, length(bus.dates), n.tranches)
- forward.deltas <- matrix(0, length(bus.dates), n.tranches)
- gammas <- matrix(0, length(bus.dates), n.tranches)
- thetas <- matrix(0, length(bus.dates), n.tranches)
- rhos <- matrix(0, length(bus.dates), n.tranches)
- corr01 <- matrix(0, length(bus.dates), n.tranches)
- durations <- matrix(0, length(bus.dates), n.tranches)
- ELmat <- matrix(0, length(bus.dates), n.tranches)
-
- for(i in seq_along(bus.dates)){
- tradedate <- bus.dates[i]
cat("calibrating", index.name, tenor, "for", as.character(tradedate), "\n", sep=" ")
exportYC(tradedate)
index <- creditIndex(index.name, tenor)
index <- set.index.desc(index, tradedate)
- ## calibrate the single names curves
+ ## calibrate the single names curvesca
index <- set.singlenamesdata(index, tradedate)
index <- set.tranchedata(index, tradedate)
- indexBasis[i] <- index$basis
- indexEL[i] <- EL(index)
- indexTheta[i] <- index$theta <- indextheta(index, tradedate)
+ index$EL <- EL(index)
+ index$theta <- indextheta(index, tradedate)
+
## calibrate the tranches using base correlation
index$rho <- build.skew(index)
- index <- c(index, BCtranche.delta(index))
- deltas[i,] <- index$deltas
- gammas[i,] <- index$gammas
- index<- c(index, BCtranche.theta(index, method="TLP"))
- thetas[i,] <- index$thetas
- forward.deltas[i,] <- index$forward.deltas
- rhos[i,] <- index$rho[-1]
- corr01[i,] <- index$corr01 <- BCtranche.corr01(index)
+
+ ## compute various risk numbers
+ index$tranches <- cbind(index$tranches, BCtranche.delta(index))
+ index$tranches <- cbind(index$tranches, BCtranche.theta(index, method="TLP"))
+ index$tranches$corr01 <- BCtranche.corr01(index)
temp <- BCtranche.pv(index, protection=TRUE)
- durations[i,] <- index$tranche.durations <-
- (temp$cl-cdsAccrued(tradedate, index$tranche.running))/index$tranche.running
- ELmat[i,] <- index$tranche.EL <- -temp$pl*diff(index$K)
+ index$tranches$duration <-
+ (temp$cl-cdsAccrued(tradedate, index$tranches$running))/index$tranches$running
+ index$tranches$EL <- -temp$pl*diff(index$K)
+
+ ## save the index object
save(index, file=file.path(root.dir, "Tranche_data", "Objects",
paste0(paste(index.name, tenor, as.character(tradedate), sep="_"),".RData")))
+
+ ## save risk numbers into the csv file
+ if(!updateflag && i==1){
+ cat(csvheaders(index), "\n", file=filename)
+ }
+ cat(tocsv(index), "\n", file=filename, append=TRUE)
cat("done\n")
}
-
- risk.numbers <- data.frame(deltas, forward.deltas, gammas, thetas, rhos, corr01, durations, ELmat)
- colnames(risk.numbers) <- c(paste(tranche.names, "Model Delta"),
- paste(tranche.names, "Forward Deltas"),
- paste(tranche.names, "Gamma"),
- paste(tranche.names, "Theta"),
- paste(Attach, "Corr"),
- paste(tranche.names, "Corr01"),
- paste(tranche.names, "Dur"),
- paste(tranche.names, "EL"))
- data <- cbind(bus.dates, quotes, indexBasis, indexEL, indexTheta, risk.numbers)
- colnames(data)[1] <- "date"
-
- write.table(data, file=file.path(root.dir,"Tranche_data","Runs", paste(index.name,tenor,"csv",sep=".")),
- append=updateflag, col.names=!updateflag, qmethod="double", sep=",", row.names=FALSE)
}
diff --git a/R/creditIndex.R b/R/creditIndex.R index 9748d6e4..b1f15a42 100644 --- a/R/creditIndex.R +++ b/R/creditIndex.R @@ -35,21 +35,19 @@ print.creditIndex <- function(index){ cat("losstodate:", index$loss, "\n\n") } if("quotes" %in% names(index)){ - cat("Index ref:", index$quotes$price*100, "\n") + cat("Index ref:", index$quotes$ref, "\n") cat("Index basis:", index$basis, "\n\n") } - row <- paste(index$K.orig[-length(index$K.orig)]*100, index$K.orig[-1]*100, sep="-") ##mapping to some prettier names - colnames.toprint <- c("tranche.upf", "tranche.running", "thetas", "deltas", - "forward.deltas", "gammas", "rho", "corr01") - short.names <- c("upfront", "running", "theta", "delta", "fw.delta","gamma", "rho", "corr01") - names(short.names) <- colnames.toprint - colnames.available <- names(index)[names(index) %in% colnames.toprint] + colnames.toprint <- c("upfront", "running", "mkt.delta", "delta", + "gamma", "theta", "corr01") + available.colnames <- colnames.toprint[colnames.toprint %in% names(index$tranches)] + df <- index$tranches[available.colnames] ##FIXME: need to check if it's bottom-up or top-down - index$rho <- index$rho[-1] - df <- data.frame(index[colnames.available], row.names=row) - names(df) <- short.names[colnames.available] + if(!is.null(index$rho)){ + df <- cbind(df, data.frame(rho=index$rho[-1])) + } print(df, digits=4) } @@ -59,3 +57,35 @@ load.index <- function(name, tenor, date){ paste0(paste(name, tenor, date, sep="_"),".RData"))) return(index) } + +csvheaders <- function(index){ + if(class(index)!="creditIndex"){ + stop("argument needs to be of class creditIndex") + } + tranche.names <- row.names(index$tranches) + headers <- c("date", "indexprice", "indexref", "indexBasis", "indexEL", "indexTheta", + paste(tranche.names, "Upfront"), + paste(tranche.names, "Dealer Delta"), + paste(tranche.names, "Model Delta"), + paste(tranche.names, "Forward Deltas"), + paste(tranche.names, "Gamma"), + paste(tranche.names, "Theta"), + paste(index$K.orig[-1]*100, "Corr"), + paste(tranche.names, "Corr01"), + paste(tranche.names, "Dur"), + paste(tranche.names, "EL")) + return(paste(headers, collapse=",")) +} + +tocsv <- function(index){ + ##write a one line csv representation of the index object + if(class(index)!="creditIndex"){ + stop("argument needs to be of class creditIndex") + } + row <- c(as.character(index$tradedate), index$quotes$price, index$quotes$ref, index$basis, + index$EL, index$theta, + unlist(index$tranches[c("upfront", "mkt.delta", "delta", "fw.delta","gamma", + "theta")]), index$rho[-1], + unlist(index$tranches[c("corr01", "duration", "EL")])) + return(paste(row, collapse=",")) +} |
