File: bermudan.R

package info (click to toggle)
rquantlib 0.4.17-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 1,308 kB
  • sloc: cpp: 3,690; sh: 69; makefile: 6; ansic: 4
file content (183 lines) | stat: -rw-r--r-- 7,566 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
##  RQuantLib function BermudanSwaption
##
##  Copyright (C) 2005         Dominick Samperi
##  Copyright (C) 2007 - 2014  Dirk Eddelbuettel
##  Copyright (C) 2016         Terry Leitch
##
##  This file is part of RQuantLib.
##
##  RQuantLib 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.
##
##  RQuantLib 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 General Public License for more details.
##
##  You should have received a copy of the GNU General Public License
##  along with RQuantLib.  If not, see <http://www.gnu.org/licenses/>.

BermudanSwaption <- function(params, ts, swaptionMaturities,
                             swapTenors, volMatrix) {
    UseMethod("BermudanSwaption")
}

BermudanSwaption.default <- function(params, ts, swaptionMaturities,
                                     swapTenors, volMatrix) {
    # Check that params list names

        if (!is.list(params) || length(params) == 0) {
            stop("The params parameter must be a non-empty list", call.=FALSE)
        }
        if(is.null(params$startDate)){
            params$startDate=advance("UnitedStates",params$tradeDate, 1, 3)
            warning("swaption start date not set, defaulting to 1 year from trade date using US calendar")
        }
        if(is.null(params$maturity)){
            params$maturity=advance("UnitedStates",params$startDate, 5, 3)
            warning("swaption maturity not set, defaulting to 5 years from startDate using US calendar")
        }
    matYears=as.numeric(params$maturity-params$tradeDate)/365
    expYears=as.numeric(params$startDate-params$tradeDate)/365
    increment=min(matYears/6,1.0)
    numObs=floor(matYears/increment)+1
    optStart=as.numeric(params$startDate-params$tradeDate)/365

    # find closest option to our target to ensure it is in calibration
    tenor=expiry=vol=vector(length=numObs,mode="numeric")

    expiryIDX=findInterval(expYears,swaptionMaturities)
    tenorIDX=findInterval(matYears-expYears,swapTenors)
    if(tenorIDX >0 & expiryIDX>0){
        vol[1]=volMatrix[expiryIDX,tenorIDX]
        expiry[1]=swaptionMaturities[expiryIDX]
        tenor[1]=swapTenors[tenorIDX]
    } else {
        vol[1]=expiry[1]=tenor[1]=0
    }

    for(i in 2:numObs){
        expiryIDX=findInterval(i*increment,swaptionMaturities)
        tenorIDX=findInterval(matYears-(i-1)*increment,swapTenors)
        if(tenorIDX >0 & expiryIDX>0){
            vol[i]=volMatrix[expiryIDX,tenorIDX]
            expiry[i]=swaptionMaturities[expiryIDX]
            tenor[i]=swapTenors[tenorIDX]

        } else {
            vol[i]=volMatrix[expiryIDX,tenorIDX+1]
            expiry[i]=swaptionMaturities[expiryIDX]
            tenor[i]=swapTenors[tenorIDX+1]
        }
    }

    # remove if search was out of bounds
    expiry=expiry[expiry>0];tenor=tenor[tenor>0];vol=vol[vol>0]
    if(length(expiry)<5){
        warning("Insufficent vols to fit affine model")
        return(NULL)
    }
    #Take 1st 5 which includes closest to initial date
    expiry=expiry[1:5];tenor=tenor[1:5];vol=vol[1:5]

#
# Check that the term structure quotes are properly formatted.
#         if(is)
#             if (!is.list(ts) || length(ts) == 0) {
#                 stop("Term structure quotes must be a non-empty list", call.=FALSE)
#             }
#         if (length(ts) != length(names(ts))) {
#             stop("Term structure quotes must include labels", call.=FALSE)
#         }
#         if (!is.numeric(unlist(ts))) {
#             stop("Term structure quotes must have numeric values", call.=FALSE)
#         }



    # Check for correct matrix/vector types
    if (!is.matrix(volMatrix)
        || !is.vector(swaptionMaturities)
        || !is.vector(swapTenors)) {
        stop("Swaption vol must be a matrix, maturities/tenors must be vectors",
             call.=FALSE)
    }

    # Check that matrix/vectors have compatible dimensions
    if (prod(dim(volMatrix)) != length(swaptionMaturities)*length(swapTenors)) {
        stop("Dimensions of swaption vol matrix not compatible with maturity/tenor vectors",
             call.=FALSE)
    }

    # Finally ready to make the call...
    # We could coerce types here and pass as.integer(round(swapTenors)),
    # temp <- as.double(volMatrix), dim(temp) < dim(a) [and pass temp instead
    # of volMatrix]. But this is taken care of in the C/C++ code.
    if (inherits(ts, "DiscountCurve")) {
        val <- bermudanWithRebuiltCurveEngine(params, c(ts$table$date), ts$table$zeroRates,
                                      swaptionMaturities,
                                      swapTenors, volMatrix)
    } else{
        if (!is.numeric(ts) | length(ts) !=1) {
            stop("Flat Term structure yield must have single numeric value", call.=FALSE)
        }
        val <- bermudanFromYieldEngine(params, ts,
                                  swaptionMaturities,
                                  swapTenors, volMatrix)
    }
    class(val) <- c(params$method, "BermudanSwaption")
    val
}

summary.G2Analytic <- function(object,...) {
    cat('\n\tSummary of pricing results for Bermudan Swaption\n')
    cat('\nPrice (in bp) of Bermudan swaption is ', object$price)
    cat('\nStike is ', format(object$params$strike,digits=6))
    cat(' (ATM strike is ', format(object$ATMStrike,digits=6), ')')
    cat('\nModel used is: G2/Jamshidian using analytic formulas')
    cat('\nCalibrated model parameters are:')
    cat('\na = ', format(object$a,digits=4))
    cat('\nb = ', format(object$b,digits=4))
    cat('\nsigma = ', format(object$sigma,digits=4))
    cat('\neta = ', format(object$eta,digits=4))
    cat('\nrho = ', format(object$rho,digits=4))
    cat('\n\n')
}

summary.HWAnalytic <- function(object,...) {
    cat('\n\tSummary of pricing results for Bermudan Swaption\n')
    cat('\nPrice (in bp) of Bermudan swaption is ', object$price)
    cat('\nStike is ', format(object$params$strike,digits=6))
    cat(' (ATM strike is ', format(object$ATMStrike,digits=6), ')')
    cat('\nModel used is: Hull-White using analytic formulas')
    cat('\nCalibrated model parameters are:')
    cat('\na = ', format(object$a,digits=4))
    cat('\nsigma = ', format(object$sigma,digits=4))
    cat('\n\n')
}

summary.HWTree <- function(object,...) {
    cat('\n\tSummary of pricing results for Bermudan Swaption\n')
    cat('\nPrice (in bp) of Bermudan swaption is ', object$price)
    cat('\nStike is ', format(object$params$strike,digits=6))
    cat(' (ATM strike is ', format(object$ATMStrike,digits=6), ')')
    cat('\nModel used is: Hull-White using a tree')
    cat('\nCalibrated model parameters are:')
    cat('\na = ', format(object$a,digits=4))
    cat('\nsigma = ', format(object$sigma,digits=4))
    cat('\n\n')
}

summary.BKTree <- function(object,...) {
    cat('\n\tSummary of pricing results for Bermudan Swaption\n')
    cat('\nPrice (in bp) of Bermudan swaption is ', object$price)
    cat('\nStike is ', format(object$params$strike,digits=6))
    cat(' (ATM strike is ', format(object$ATMStrike,digits=6), ')')
    cat('\nModel used is: Black-Karasinski using a tree')
    cat('\nCalibrated model parameters are:')
    cat('\na = ', format(object$a,digits=4))
    cat('\nsigma = ', format(object$sigma,digits=4))
    cat('\n\n')
}