Cox-Ross-Rubinstein (Binomial Option Price) Model


 

     
 

In this example, we derived call and put option price using the binomial model, also known as the Cox-Ross-Rubinstein option model. The outcomes are shown in a format similar to that used for example 6. Note that binomial distribution will become normal when the number of steps (n) becomes large. Hence, when n increases, both of the call and put option prices estimated from the binomial model come close to the prices estimated from the Black-Scholes model. This phenomenon is shown on Figure 1. For example, the option prices estimated using the binomial model with 1,000 steps (in cells K13..K14) are equivalent (to 3 decimal places) to the prices estimated from the Black-Scholes model in cells H23..H24.

'************************************************************************
'*                                   Binomial European Call Price                            *
'************************************************************************

Function Bi_Call_Eur(s, x, t, r, sd, n As Integer)
    Dim sdd As Single
    Dim j As Integer
    Dim rr As Single
    Dim q As Single
    Dim u As Single
    Dim d As Single
    Dim bicomp As Single
    Dim sumbi As Single
    Dim nj As Double
    Dim firstBicomp As Single
   
    rr = Exp(r * (t / n)) - 1
    sdd = sd * Sqr(t / n)
    u = Exp(rr + sdd)
    d = Exp(rr - sdd)
    q = (1 + rr - d) / (u - d)
   
    For j = 0 To n
        nj = binoCoeff(n, j)
        bicomp = nj * (q ^ j) * ((1 - q) ^ (n - j)) * (s * (u ^ j) * (d ^ (n - j)) - x)
        If bicomp < 0 Then bicomp = 0
        sumbi = sumbi + bicomp
    Next j
   
    Bi_Call_Eur = sumbi / ((1 + rr) ^ n)
         
End Function


'*********************************************************************
'*                               Binomial European Put Price                            *
'*********************************************************************

Function Bi_Put_Eur(s, x, t, r, sd, n As Integer)
    Dim sdd As Single
    Dim j As Integer
    Dim rr As Single
    Dim q As Single
    Dim u As Single
    Dim d As Single
    Dim bicomp As Single
    Dim sumbi As Single
    Dim nj As Double
    Dim firstBicomp As Single
   
    rr = Exp(r * (t / n)) - 1
    sdd = sd * Sqr(t / n)
    u = Exp(rr + sdd)
    d = Exp(rr - sdd)
    q = (1 + rr - d) / (u - d)
   
    For j = 0 To n
        nj = binoCoeff(n, j)
        bicomp = nj * (q ^ j) * ((1 - q) ^ (n - j)) * (x - (s * (u ^ j) * (d ^ (n - j))))
        If bicomp < 0 Then bicomp = 0
        sumbi = sumbi + bicomp
    Next j
   
    Bi_Put_Eur = sumbi / ((1 + rr) ^ n)
   
End Function


'************************************************************************
'*                                  Compute Binomial Coefficient                            *
'*     (this function provides similar result as COMBIN( ) on Excel)   *
'************************************************************************

Function binoCoeff(n, j)
          Dim i As Integer
          Dim b As Double
         
          b = 1
          For i = 0 To j - 1
                    b = b * (n - i) / (j - i)
          Next i
          binoCoeff = b
         
End Function


VBA Codes