[R] Loop and Solver with Black/Scholes-Formula

Berend Hasselman bhh at xs4all.nl
Sat Apr 23 21:51:49 CEST 2011


bstudent wrote:
> 
> Hello,
> 
> for my diploma thesis I need to program a solver for Merton´s respectively
> Black´s and Scholes´ Option pricing formula, which should be achieved for
> several dates.
> 
> What I want to do is to estimate the value of a firm´s assets "vA" (x[2]
> denotes vA) and the option-implied volatility of firm´s assets "sigA"
> (x[1] denotes sigA) by solving it simultaneous using the Black and Scholes
> formulas. This solution should be computed for several dates, at which the
> data input changes with the next date (it should be computed row by row of
> the data input matrix).
> 
> What I did so far is to program a for-loop in which I wrote the solver:
> 
>># Dataset:
>>
>> head(citin)
>    Q       vE           sigE           D             R
> 1  1  39.81095  0.08957312  51.64004  0.00930000
> 2  2  39.76028  0.09127646  54.98504  0.01072000
> 3  3  37.00382  0.08177820  60.29025  0.01489545
> 4  4  35.17477  0.09221447  60.41061  0.02017879
> 5  5  36.54418  0.07852334  55.00648  0.02553438
> 6  6  37.20026  0.07949604  62.59768  0.02908462
>> 
>>
>>
>># Loop with Solver for 6 dates:
>>
>> citinbs <- for (i in 1:6) {
> + 
> + BS <- function(x) {
> + 
> + vE   <- citin[i,2]
> + sigE <- citin[i,3]
> + D    <- citin[i,4]
> + R    <- citin[i,5]
> + 
> + T = 1
> + 
> + f <- rep(NA, length(x))
> + 
> + f[1] <- (x[1] * pnorm(log (x[1]/D) + (R + ( (x[1]^2) / 2) ) * T ) / (
> x[2] * sqrt(T)) - exp(-R*T) * D * pnorm(log (x[1]/D) + (R - ( (x[1]^2) /
> 2) ) * T ) / ( x[2] * sqrt(T))) - vE
> + 
> + f[2] <- ((x[1] * exp(-T) * pnorm(log (x[1]/D) + (R + ( (x[1]^2) / 2) ) *
> T ) / ( x[2] * sqrt(T)) * x[2]) / vE) - sigE
> + 
> + f
> + }
> + 
> + p0 <- c( vE + D, sigE * (vE / (vE + D)) )
> + 
> + ans <- dfsane(par=p0, fn=BS)
> + 
> + print(as.matrix(ans$par))
> + 
> + }
> 
> 
> The problem is, that the results I get aren´t really plausible. The next
> thing is, that I need the relevant Values of Output (ans$par, which
> includes two values - x[1]=vA and x[2]=sigA - per date) as matrix. This
> Matrix should look like this:
> 
> vA   sigA
> 
> a     x
> b     y
> c     z
> .     .
> .     .
> .     .
> 
> The entry I wrote ("print(as.matrix(ans$par))") doesn´t achieve that.
> 
> 
> I hope you understood what I´m trying to do. I´m an absolute beginner in
> programming in R, so these are some of my first steps. Please be patient
> ;)
> Also I hope my English isn´t to bad.
> 
> Thank you very much for helping me out!!!
> 
> Kind regards,
> 
> bstudent.
> 

Your example is not reproducible since you haven't shown the source of a
runnable R script.
Statements are missing such as library(BB)
Furthermore the code within the loop is wrong and will lead to an error
message since vE, etc used in the calculation of p0 are only defined in the
body of the function BS.

I tried the following code where no attempt is made to store anything in a
matrix but only the return value of dfsane is printed to see what dfsane
achieved. You will see that dfsane can't solve your system of equations. I'm
not sufficiently knowledgable about dfsane to tweak dfsane to see if it can
find a solution.


library(BB)
library(nleqslv)  #solve system of equations with Broyden/Newton; install
from CRAN

citin.txt <- "Q vE sigE D R
1  39.81095  0.08957312  51.64004  0.00930000
2  39.76028  0.09127646  54.98504  0.01072000
3  37.00382  0.08177820  60.29025  0.01489545
4  35.17477  0.09221447  60.41061  0.02017879
5  36.54418  0.07852334  55.00648  0.02553438
6  37.20026  0.07949604  62.59768  0.02908462"

citin <- read.table(textConnection(citin.txt), header=TRUE,
stringsAsFactors=FALSE)
citin

# Loop with Solver for 6 dates:

for (i in 1:6) {
    vE   <- citin[i,2]
    sigE <- citin[i,3]
    D    <- citin[i,4]
    R    <- citin[i,5]

    BS <- function(x) {
        T = 1
        f <- rep(NA, length(x))

        f[1] <- (x[1] * pnorm(log (x[1]/D) + (R + ( (x[1]^2) / 2) ) * T ) /
( x[2] * sqrt(T)) - exp(-R*T) * D * pnorm(log (x[1]/D) + (R - ( (x[1]^2) /
2) ) * T ) / ( x[2] * sqrt(T))) - vE
        f[2] <- ((x[1] * exp(-T) * pnorm(log (x[1]/D) + (R + ( (x[1]^2) / 2)
) * T ) / ( x[2] * sqrt(T)) * x[2]) / vE) - sigE
        f
    }

    p0 <- c( vE + D, sigE * (vE / (vE + D)) ) 
    print(p0)
    ans <- dfsane(par=p0, fn=BS)
    print(ans)
}

If you replace the  line with dfsane with

    ans <- nleqslv(p0,BS)

you will see that nleqslv is able to solve your problem.


Berend



 


--
View this message in context: http://r.789695.n4.nabble.com/Loop-and-Solver-with-Black-Scholes-Formula-tp3470488p3470556.html
Sent from the R help mailing list archive at Nabble.com.



More information about the R-help mailing list