Skip to main content

Binomial OPM, Black–Scholes OPM, and Their Relationship: Decision Tree and Microsoft Excel Approach

  • Reference work entry
  • First Online:
Handbook of Financial Econometrics and Statistics
  • 9132 Accesses

Abstract

This chapter will first demonstrate how Microsoft Excel can be used to create the decision trees for the binomial option pricing model. At the same time, this chapter will discuss the binomial option pricing model in a less mathematical fashion. All the mathematical calculations will be taken care by the Microsoft Excel program that is presented in this chapter. Finally, this chapter also uses the decision tree approach to demonstrate the relationship between the binomial option pricing model and the Black–Scholes option pricing model.

This is a preview of subscription content, log in via an institution to check access.

Access this chapter

Chapter
USD 29.95
Price excludes VAT (USA)
  • Available as PDF
  • Read on any device
  • Instant download
  • Own it forever
eBook
USD 849.99
Price excludes VAT (USA)
  • Available as EPUB and PDF
  • Read on any device
  • Instant download
  • Own it forever
Hardcover Book
USD 549.99
Price excludes VAT (USA)
  • Durable hardcover edition
  • Dispatched in 3 to 5 business days
  • Free shipping worldwide - see info

Tax calculation will be finalised at checkout

Purchases are for personal use only

Institutional subscriptions

Notes

  1. 1.

    Please note that in Lee et al. (2000, p. 234) u = 1 + percentage of price increase and d = 1 – percentage of price increase.

References

  • Benninga, S. (2000). Financial modeling. Cambridge: MIT Press.

    Google Scholar 

  • Benninga, S. (2008). Financial modeling. Cambridge: MIT Press.

    Google Scholar 

  • Black, F., & Scholes, M. (1973). The pricing of options and corporate liabilities. Journal of Political Economy, 31, 637–659.

    Article  Google Scholar 

  • Cox, J., Ross, S. A., & Rubinstein, M. (1979). Option pricing: A simplified approach. Journal of Financial Economics, 7, 229–263.

    Article  Google Scholar 

  • Daigler, R. T. (1994). Financial futures and options markets concepts and strategies. New York: Harper Collins.

    Google Scholar 

  • Jarrow, R., & TurnBull, S. (1996). Derivative securities. Cincinnati: South-Western College Publishing.

    Google Scholar 

  • Lee, J. C. (2001). Using Microsoft excel and decision trees to demonstrate the binomial option pricing model. Advances in Investment Analysis and Portfolio Management, 8, 303–329.

    Google Scholar 

  • Lee, C. F. (2009). Handbook of quantitative finance. New York: Springer.

    Google Scholar 

  • Lee, C. F., & Lee, A. C. (2006). Encyclopedia of finance. New York: Springer.

    Book  Google Scholar 

  • Lee, C. F., Lee, J. C., & Lee, A. C. (2000). Statistics for business and financial economics. New Jersey: World Scientific.

    Google Scholar 

  • Lee, J. C., Lee, C. F., Wang, R. S., & Lin, T. I. (2004). On the limit properties of binomial and multinomial option pricing models: Review and integration. In C. F. Lee (Ed.), Advances in quantitative analysis of finance and accounting new series (Vol. 1). Singapore: World Scientific.

    Google Scholar 

  • Rendleman, R. J., Jr., & Barter, B. J. (1979). Two-state option pricing. Journal of Finance, 34(5), 1093–1110.

    Article  Google Scholar 

  • Walkenbach, J. (2010). Excel 2010 power programming with VBA. Indianapolis: Wiley.

    Book  Google Scholar 

  • Wells, E., & Harshbarger, S. (1997). Microsoft excel 97 developer’s handbook. Redmond: Microsoft Press.

    Google Scholar 

Download references

Author information

Authors and Affiliations

Authors

Corresponding author

Correspondence to John C. Lee .

Editor information

Editors and Affiliations

Appendix 1: Excel VBA Code: Binomial Option Pricing Model

Appendix 1: Excel VBA Code: Binomial Option Pricing Model

It is important to note that the thing that makes Microsoft Excel powerful is that it offers a powerful professional programming language called Visual Basic for Applications (VBA). This section shows the VBA code that generated the decision trees for the binomial option pricing model. This code is in the form frmBinomiaOption. The procedure cmdCalculate_Click is the first procedure to run.

'/**************************************************

'/ Relationship Between the Binomial OPM

'/ and Black-Scholes OPM:

'/ Decision Tree and Microsoft Excel Approach

'/

'/ by John Lee

'/ JohnLeeExcelVBA@gmail.com

'/ All Rights Reserved

'/**************************************************

Option Explicit

Dim mwbTreeWorkbook As Workbook

Dim mwsTreeWorksheet As Worksheet

Dim mwsCallTree As Worksheet

Dim mwsPutTree As Worksheet

Dim mwsBondTree As Worksheet

Dim mdblPFactor As Double

Dim mBinomialCalc As Long

Dim mCallPrice As Double 'jcl 12/8/2008

Dim mPutPrice As Double 'jcl 12/8/2008

'/**************************************************

'/Purpose: Keep track the numbers of binomial calc

'/**************************************************

Property Let BinomialCalc(l As Long)

mBinomialCalc = l

End Property

Property Get BinomialCalc() As Long

BinomialCalc = mBinomialCalc

End Property

Property Set TreeWorkbook(wb As Workbook)

Set mwbTreeWorkbook = wb

End Property

Property Get TreeWorkbook() As Workbook

Set TreeWorkbook = mwbTreeWorkbook

End Property

Property Set TreeWorksheet(ws As Worksheet)

Set mwsTreeWorksheet = ws

End Property

Property Get TreeWorksheet() As Worksheet

Set TreeWorksheet = mwsTreeWorksheet

End Property

Property Set CallTree(ws As Worksheet)

Set mwsCallTree = ws

End Property

Property Get CallTree() As Worksheet

Set CallTree = mwsCallTree

End Property

Property Set PutTree(ws As Worksheet)

Set mwsPutTree = ws

End Property

Property Get PutTree() As Worksheet

Set PutTree = mwsPutTree

End Property

Property Set BondTree(ws As Worksheet)

Set mwsBondTree = ws

End Property

Property Get BondTree() As Worksheet

Set BondTree = mwsBondTree

End Property

Property Let CallPrice(dCallPrice As Double)

'12/8/2008

mCallPrice = dCallPrice

End Property

Property Get CallPrice() As Double

Let CallPrice = mCallPrice

End Property

Property Let PutPrice(dPutPrice As Double)

'12/10/2008

mPutPrice = dPutPrice

End Property

Property Get PutPrice() As Double

'12/10/2008

Let PutPrice = mPutPrice

End Property

Property Let PFactor(r As Double)

Dim dRate As Double

dRate = ((1 + r) - Me.txtBinomialD) / (Me.txtBinomialU - Me.txtBinomialD)

Let mdblPFactor = dRate

End Property

Property Get PFactor() As Double

Let PFactor = mdblPFactor

End Property

Property Get qU() As Double

Dim dblDeltaT As Double

Dim dblDown As Double

Dim dblUp As Double

Dim dblR As Double

dblDeltaT = Me.txtTimeT / Me.txtBinomialN

dblR = Exp(Me.txtBinomialr * dblDeltaT)

dblUp = Exp(Me.txtSigma * VBA.Sqr(dblDeltaT))

dblDown = Exp(-Me.txtSigma * VBA.Sqr(dblDeltaT))

qU = (dblR - dblDown) / (dblR * (dblUp - dblDown))

End Property

Property Get qD() As Double

Dim dblDeltaT As Double

Dim dblDown As Double

Dim dblUp As Double

Dim dblR As Double

dblDeltaT = Me.txtTimeT / Me.txtBinomialN

dblR = Exp(Me.txtBinomialr * dblDeltaT)

dblUp = Exp(Me.txtSigma * VBA.Sqr(dblDeltaT))

dblDown = Exp(-Me.txtSigma * VBA.Sqr(dblDeltaT))

qD = (dblUp - dblR) / (dblR * (dblUp - dblDown))

End Property

Private Sub chkBinomialBSApproximation_Click()

On Error Resume Next

'Time and Sigma only BlackScholes parameter

Me.txtTimeT.Visible = Me.chkBinomialBSApproximation

Me.lblTimeT.Visible = Me.chkBinomialBSApproximation

Me.txtSigma.Visible = Me.chkBinomialBSApproximation

Me.lblSigma.Visible = Me.chkBinomialBSApproximation

txtTimeT_Change

End Sub

Private Sub cmdCalculate_Click()

Me.Hide

BinomialOption

Unload Me

End Sub

Private Sub cmdCancel_Click()

Unload Me

End Sub

Private Sub txtBinomialN_Change()

'jcl 12/8/2008

On Error Resume Next

If Me.chkBinomialBSApproximation Then

Me.txtBinomialU = Exp(Me.txtSigma * Sqr(Me.txtTimeT / Me.txtBinomialN))

Me.txtBinomialD = Exp(-Me.txtSigma * Sqr(Me.txtTimeT / Me.txtBinomialN))

End If

End Sub

Private Sub txtTimeT_Change()

'jcl 12/8/2008

On Error Resume Next

If Me.chkBinomialBSApproximation Then

Me.txtBinomialU = Exp(Me.txtSigma * Sqr(Me.txtTimeT / Me.txtBinomialN))

Me.txtBinomialD = Exp(-Me.txtSigma * Sqr(Me.txtTimeT / Me.txtBinomialN))

End If

End Sub

Private Sub UserForm_Initialize()

With Me

.txtBinomialS = 20

.txtBinomialX = 20

.txtBinomialD = 0.95

.txtBinomialU = 1.05

.txtBinomialN = 4

.txtBinomialr = 0.03

.txtSigma = 0.2

.txtTimeT = 4

Me.chkBinomialBSApproximation = False

End With

chkBinomialBSApproximation_Click

Me.Hide

End Sub

Sub BinomialOption()

Dim wbTree As Workbook

Dim wsTree As Worksheet

Dim rColumn As Range

Dim ws As Worksheet

Set Me.TreeWorkbook = Workbooks.Add

Set Me.BondTree = Me.TreeWorkbook.Worksheets.Add

Set Me.PutTree = Me.TreeWorkbook.Worksheets.Add

Set Me.CallTree = Me.TreeWorkbook.Worksheets.Add

Set Me.TreeWorksheet = Me.TreeWorkbook.Worksheets.Add

Set rColumn = Me.TreeWorksheet.Range("a1")

With Me

.BinomialCalc = 0

.PFactor = Me.txtBinomialr

.CallTree.Name = "Call Option Price"

.PutTree.Name = "Put Option Price"

.TreeWorksheet.Name = "Stock Price"

.BondTree.Name = "Bond"

End With

DecisionTree rCell:=rColumn, nPeriod:=Me.txtBinomialN + 1, _

dblPrice:=Me.txtBinomialS, sngU:=Me.txtBinomialU, _

sngD:=Me.txtBinomialD

DecitionTreeFormat

TreeTitle wsTree:=Me.TreeWorksheet, sTitle:="Stock Price "

TreeTitle wsTree:=Me.CallTree, sTitle:="Call Option Pricing"

TreeTitle wsTree:=Me.PutTree, sTitle:="Put Option Pricing"

TreeTitle wsTree:=Me.BondTree, sTitle:="Bond Pricing"

Application.DisplayAlerts = False

For Each ws In Me.TreeWorkbook.Worksheets

If Left(ws.Name, 5) = "Sheet" Then

ws.Delete

Else

ws.Activate

ActiveWindow.DisplayGridlines = False

ws.UsedRange.NumberFormat = "#,##0.0000_);(#,##0.0000)"

End If

Next

Application.DisplayAlerts = True

Me.TreeWorksheet.Activate

End Sub

Sub TreeTitle(wsTree As Worksheet, sTitle As String)

wsTree.Range("A1:A5").EntireRow.Insert (xlShiftDown)

With wsTree

With.Cells(1)

.Value = sTitle

.Font.Size = 20

.Font.Italic = True

End With

With.Cells(2, 1)

.Value = "Decision Tree"

.Font.Size = 16

.Font.Italic = True

End With

With.Cells(3, 1)

.Value = "Price = " & Me.txtBinomialS & _

",Exercise = " & Me.txtBinomialX & _

",U = " & Format(Me.txtBinomialU, "#,##0.0000") & _

",D = " & Format(Me.txtBinomialD, "#,##0.0000") & _

",N = " & Me.txtBinomialN & _

",R = " & Me.txtBinomialr

.Font.Size = 14

End With

With.Cells(4, 1)

.Value = "Number of calculations: " & Me.BinomialCalc

.Font.Size = 14

End With

If wsTree Is Me.CallTree Then

With.Cells(5, 1)

.Value = "Binomial Call Price= " & Format(Me.CallPrice, "#,##0.0000")

.Font.Size = 14

End With

If Me.chkBinomialBSApproximation Then

wsTree.Range("A6:A7").EntireRow.Insert (xlShiftDown)

With.Cells(6, 1)

.Value = "Black-Scholes Call Price= " & Format(Me.BS_Call, "#,##0.0000") _

& ",d1=" & Format(Me.BS_D1, "#,##0.0000") _

& ",d2=" & Format(Me.BS_D2, "#,##0.0000") _

& ",N(d1)=" & Format(WorksheetFunction.NormSDist(BS_D1), "#,##0.0000") _

& ",N(d2)=" & Format(WorksheetFunction.NormSDist(BS_D2), "#,##0.0000")

.Font.Size = 14

End With

End If

ElseIf wsTree Is Me.PutTree Then

With.Cells(5, 1)

.Value = "Binomial Put Price: " & Format(Me.PutPrice, "#,##0.0000")

.Font.Size = 14

End With

If Me.chkBinomialBSApproximation Then

wsTree.Range("A6:A7").EntireRow.Insert (xlShiftDown)

With.Cells(6, 1)

.Value = "Black-Scholes Put Price: " & Format(Me.BS_PUT, "#,##0.0000")

.Font.Size = 14

End With

End If

End If

End With

End Sub

Sub BondDecisionTree(rPrice As Range, arCell As Variant, iCount As Long)

Dim rBond As Range

Dim rPup As Range

Dim rPDown As Range

Set rBond = Me.BondTree.Cells(rPrice.Row, rPrice.Column)

Set rPup = Me.BondTree.Cells(arCell(iCount - 1).Row, arCell(iCount - 1).Column)

Set rPDown = Me.BondTree.Cells(arCell(iCount).Row, arCell(iCount).Column)

If rPup.Column = Me.TreeWorksheet.UsedRange.Columns.Count Then

rPup.Value = (1 + Me.txtBinomialr) ^ (rPup.Column - 1)

rPDown.Value = rPup.Value

End If

With rBond

.Value = (1 + Me.txtBinomialr) ^ (rBond.Column - 1)

.Borders(xlBottom).LineStyle = xlContinuous

End With

rPDown.Borders(xlBottom).LineStyle = xlContinuous

With rPup

.Borders(xlBottom).LineStyle = xlContinuous

.Offset(1, 0).Resize((rPDown.Row - rPup.Row), 1). _

Borders(xlEdgeLeft).LineStyle = xlContinuous

End With

End Sub

Sub PutDecisionTree(rPrice As Range, arCell As Variant, iCount As Long)

Dim rCall As Range

Dim rPup As Range

Dim rPDown As Range

Set rCall = Me.PutTree.Cells(rPrice.Row, rPrice.Column)

Set rPup = Me.PutTree.Cells(arCell(iCount - 1).Row, arCell(iCount - 1).Column)

Set rPDown = Me.PutTree.Cells(arCell(iCount).Row, arCell(iCount).Column)

If rPup.Column = Me.TreeWorksheet.UsedRange.Columns.Count Then

rPup.Value = WorksheetFunction.Max(Me.txtBinomialX - arCell(iCount - 1), 0)

rPDown.Value = WorksheetFunction.Max(Me.txtBinomialX - arCell(iCount), 0)

End If

With rCall

'12/10/2008

If Not Me.chkBinomialBSApproximation Then

.Value = (Me.PFactor * rPup + (1 - Me.PFactor) * rPDown) / (1 + Me.txtBinomialr)

Else

.Value = (Me.qU * rPup) + (Me.qD * rPDown)

End If

Me.PutPrice =.Value '12/8/2008

.Borders(xlBottom).LineStyle = xlContinuous

End With

rPDown.Borders(xlBottom).LineStyle = xlContinuous

With rPup

.Borders(xlBottom).LineStyle = xlContinuous

.Offset(1, 0).Resize((rPDown.Row - rPup.Row), 1). _

Borders(xlEdgeLeft).LineStyle = xlContinuous

End With

End Sub

Sub CallDecisionTree(rPrice As Range, arCell As Variant, iCount As Long)

Dim rCall As Range

Dim rCup As Range

Dim rCDown As Range

Set rCall = Me.CallTree.Cells(rPrice.Row, rPrice.Column)

Set rCup = Me.CallTree.Cells(arCell(iCount - 1).Row, arCell(iCount - 1).Column)

Set rCDown = Me.CallTree.Cells(arCell(iCount).Row, arCell(iCount).Column)

If rCup.Column = Me.TreeWorksheet.UsedRange.Columns.Count Then

With rCup

.Value = WorksheetFunction.Max(arCell(iCount - 1) - Me.txtBinomialX, 0)

.Borders(xlBottom).LineStyle = xlContinuous

End With

With rCDown

.Value = WorksheetFunction.Max(arCell(iCount) - Me.txtBinomialX, 0)

.Borders(xlBottom).LineStyle = xlContinuous

End With

End If

With rCall

If Not Me.chkBinomialBSApproximation Then

.Value = (Me.PFactor * rCup + (1 - Me.PFactor) * rCDown) / (1 + Me.txtBinomialr)

Else

.Value = (Me.qU * rCup) + (Me.qD * rCDown)

End If

Me.CallPrice =.Value '12/8/2008

.Borders(xlBottom).LineStyle = xlContinuous

End With

rCup.Offset(1, 0).Resize((rCDown.Row - rCup.Row), 1). _

Borders(xlEdgeLeft).LineStyle = xlContinuous

End Sub

Sub DecitionTreeFormat()

Dim rTree As Range

Dim nColumns As Integer

Dim rLast As Range

Dim rCell As Range

Dim lCount As Long

Dim lCellSize As Long

Dim vntColumn As Variant

Dim iCount As Long

Dim lTimes As Long

Dim arCell() As Range

Dim sFormatColumn As String

Dim rPrice As Range

Application.StatusBar = "Formatting Tree.. "

Set rTree = Me.TreeWorksheet.UsedRange

nColumns = rTree.Columns.Count

Set rLast = rTree.Columns(nColumns).EntireColumn.SpecialCells(xlCellTypeConstants, 23)

lCellSize = rLast.Cells.Count

For lCount = nColumns To 2 Step -1

sFormatColumn = rLast.Parent.Columns(lCount).EntireColumn.Address

Application.StatusBar = "Formatting column " & sFormatColumn

ReDim vntColumn(1 To (rLast.Cells.Count / 2), 1)

Application.StatusBar = "Assigning values to array for column " & _

rLast.Parent.Columns(lCount).EntireColumn.Address

vntColumn = rLast.Offset(0, -1).EntireColumn.Cells(1).Resize(rLast.Cells.Count / 2, 1)

rLast.Offset(0, -1).EntireColumn.ClearContents

ReDim arCell(1 To rLast.Cells.Count)

lTimes = 1

Application.StatusBar = "Assigning cells to arrays. Total number of cells: " & lCellSize

For Each rCell In rLast.Cells

Application.StatusBar = "Array to column " & sFormatColumn & " Cells " & rCell.Row

Set arCell(lTimes) = rCell

lTimes = lTimes + 1

Next

lTimes = 1

Application.StatusBar = "Formatting leaves for column " & sFormatColumn

For iCount = 2 To lCellSize Step 2

Application.StatusBar = "Formatting leaves for cell " & arCell(iCount).Address

If rLast.Cells.Count <> 2 Then

Set rPrice = arCell(iCount).Offset(-1 * ((arCell(iCount).Row - arCell(iCount -1).Row) / 2), -1)

rPrice.Value = vntColumn(lTimes, 1)

Else

Set rPrice = arCell(iCount).Offset(-1 * ((arCell(iCount).Row - arCell(iCount -1).Row) / 2), -1)

rPrice.Value = vntColumn

End If

arCell(iCount).Borders(xlBottom).LineStyle = xlContinuous

With arCell(iCount - 1)

.Borders(xlBottom).LineStyle = xlContinuous

.Offset(1, 0).Resize((arCell(iCount).Row - arCell(iCount - 1).Row), 1). _

Borders(xlEdgeLeft).LineStyle = xlContinuous

End With

lTimes = 1 + lTimes

CallDecisionTree rPrice:=rPrice, arCell:=arCell, iCount:=iCount

PutDecisionTree rPrice:=rPrice, arCell:=arCell, iCount:=iCount

BondDecisionTree rPrice:=rPrice, arCell:=arCell, iCount:=iCount

Next

Set rLast = rTree.Columns(lCount - 1).EntireColumn.SpecialCells(xlCellTypeConstants, 23)

lCellSize = rLast.Cells.Count

Next ' / outer next

rLast.Borders(xlBottom).LineStyle = xlContinuous

Application.StatusBar = False

End Sub

'/**************************************************

'/Purpse: To calculate the price value of every state of the binomial

'/ decision tree

'/**************************************************

Sub DecisionTree(rCell As Range, nPeriod As Integer, _

dblPrice As Double, sngU As Single, sngD As Single)

Dim lIteminColumn As Long

If Not nPeriod = 1 Then

'Do Up

DecisionTree rCell:=rCell.Offset(0, 1), nPeriod:=nPeriod - 1, _

dblPrice:=dblPrice * sngU, sngU:=sngU, _

sngD:=sngD

'Do Down

DecisionTree rCell:=rCell.Offset(0, 1), nPeriod:=nPeriod - 1, _

dblPrice:=dblPrice * sngD, sngU:=sngU, _

sngD:=sngD

End If

lIteminColumn = WorksheetFunction.CountA(rCell.EntireColumn)

If lIteminColumn = 0 Then

rCell = dblPrice

Else

If nPeriod <> 1 Then

rCell.EntireColumn.Cells(lIteminColumn + 1) = dblPrice

Else

rCell.EntireColumn.Cells(((lIteminColumn + 1) * 2) - 1) = dblPrice

Application.StatusBar = "The number of binomial calcs are : " & Me.BinomialCalc _ & " at cell " & rCell.EntireColumn.Cells(((lIteminColumn + 1) * 2) - 1).Address

End If

End If

Me.BinomialCalc = Me.BinomialCalc + 1

End Sub

Function BS_D1() As Double

Dim dblNumerator As Double

Dim dblDenominator As Double

On Error Resume Next

dblNumerator = VBA.Log(Me.txtBinomialS / Me.txtBinomialX) + _

((Me.txtBinomialr + Me.txtSigma ^ 2 / 2) * Me.txtTimeT)

dblDenominator = Me.txtSigma * Sqr(Me.txtTimeT)

BS_D1 = dblNumerator / dblDenominator

End Function

Function BS_D2() As Double

On Error Resume Next

BS_D2 = BS_D1 - (Me.txtSigma * VBA.Sqr(Me.txtTimeT))

End Function

Function BS_Call() As Double

BS_Call = (Me.txtBinomialS * WorksheetFunction.NormSDist(BS_D1)) _

- Me.txtBinomialX * Exp(-Me.txtBinomialr * Me.txtTimeT) * _

WorksheetFunction.NormSDist(BS_D2)

End Function

'Used put-call parity theorem to price put option

Function BS_PUT() As Double

BS_PUT = BS_Call - Me.txtBinomialS + _

(Me.txtBinomialX * Exp(-Me.txtBinomialr * Me.txtTimeT))

End Function

Rights and permissions

Reprints and permissions

Copyright information

© 2015 Springer Science+Business Media New York

About this entry

Cite this entry

Lee, J.C. (2015). Binomial OPM, Black–Scholes OPM, and Their Relationship: Decision Tree and Microsoft Excel Approach. In: Lee, CF., Lee, J. (eds) Handbook of Financial Econometrics and Statistics. Springer, New York, NY. https://doi.org/10.1007/978-1-4614-7750-1_37

Download citation

  • DOI: https://doi.org/10.1007/978-1-4614-7750-1_37

  • Published:

  • Publisher Name: Springer, New York, NY

  • Print ISBN: 978-1-4614-7749-5

  • Online ISBN: 978-1-4614-7750-1

  • eBook Packages: Business and Economics

Publish with us

Policies and ethics