Thursday, June 13, 2013

Implementing binomial solver design in VBA

In this long post, I will open up my current implementation for binomial option solver. The reader is expected to be familiar and comfortable with theory of pricing option by using binomial model. If you feel a bit rusty with the topic, you can get some refreshing overview from here, for example: http://en.wikipedia.org/wiki/Binomial_options_pricing_model 

Let us say, that we would like to create a program to price options by using binomial model, but keep everything as flexible as possible. This means, that we have to abandon the idea of creating one big monolithic function (traditional VBA approach). Anyway, what do we need to accomplish this, and how could we create such a design?

Components

1) Parameters source - this is a "place", from which we read in all option-related parameters. We are not hard-coding anything, but instead we are going to create interface IOptionFactory for different possible data sources. IOptionFactory has only two public methods: createOptionParameters and getOptionParameters. Hereby, it is only a container for all option-related parameters needed in this design.

In essence, we could create different interface implementations for reading parameters from system database or text file, for example. However, In this example our IOptionFactory implementation is going to be ExcelFactory class, which reads parameters from Excel Worksheet into optionParameters parameter wrapper.

Parameter wrapper is Dictionary data structure, into which we save all needed parameters in this program (remember to reference Microsoft Scripting Runtime library). For parameter wrapper, we need to have public Enumerator for all field key values used in parameter wrapper. If you have no idea what I am explaining here, check out my post http://mikejuniperhill.blogspot.fi/2013/05/handling-parameters-dynamically-with.html

2) Data structure - this is a data structure (Tree) for storing data (the actual binomial tree structure). For this purpose, we are simply wrapping jagged array (array of arrays) into a separate class. This class has only the most vital functionalities, such as access to Tree items (nodes) and information about number of Tree periods and number of states in each period. Hereby, Tree class is only a data container and for any operations to be performed on items of this container, we create separate iterator interface ITreeIterator.

By having data and algorithms separately means, that we can create new iterator implementations for operating on Tree structure nodes in a different way and we do not need to change anything in Tree class. Moreover, we can always replace any existing iterator in our design, just by plugging in a new iterator and there is no need to break the existing program design. I would say, that these benefits will clearly override the costs of implementing this scheme.

So, ITreeIterator interface has all the needed methods for performing operations on Tree nodes. The next question is, what are those operations? If we think about the pricing option with binomial method, these operations could be the following:
  1. Forward iteration - for creating the actual spot Tree.
  2. Terminal payoff calculation - for calculating option payoffs for each state at the maturity date of the option.
  3. Backward iteration - for discounting option payoffs and calculating option payoffs on each node from maturity to present date.
Creating a spot tree (forward iteration) is basically quite straightforward process. Calculating payoffs at maturity and backward iteration (option valuation parts) can be a bit more tricky issue, depending on option type. Since our iterator is an implementation, for backward iterating process we could implement different iterators, such as American iterator or Bermudan iterator for example. We can also change Payoff function to calculate any possible payoff, since it is a separate object what we are feeding to our iterator. Example Implementation given in this program is European iterator (EuropeanTreeIterator).

3) Payoff function - option payoff structure is going to be implemented also as an interface (IOneFactorPayoff). Along with its init method (artificial constructor), it has only one public method - getPayoff, which calculates option payoff for a given spot price. Example implementation is for vanilla call option (VanillaCallPayoff).

4) Binomial process parameters - as we know, there are a lot of different models for creating binomial trees. We want to leave an option for the user to use different binomial models. For this reason, we create interface ILatticeStrategy. This interface has only one public method - init (artificial constructor), which takes in parameter wrapper as argument. The purpose of this method is to create binomial process-related parameters (u, d and p) and save these back into parameter wrapper. In this example, we implement Cox-Ross-Rubinstein model without drift (CRRNoDrift).

Program flow

Now, how on earth do we manage all this mess, what I have just described? I admit, that this design candidate might feel overly complex - at first. However, after some further investigations you should see, that it is actually pretty straightforward. Well, of course not as straightforward as that traditional monolithic VBA function, but our "extra complexity" is not there without some very good reasons. Let us talk about these reasons later in our afterthoughts section. At this moment, let us try to get some sense about this design by looking our test program first.

Option Explicit
'
Sub Tester()
    '
    ' create option parameters in option factory
    Dim optionFactory As IOptionFactory: Set optionFactory = New ExcelFactory
    optionFactory.createOptionParameters
    '
   
    ' create option payoff object
    Dim payoff As IOneFactorPayoff: Set payoff = New VanillaCallPayoff
    payoff.init optionFactory.getOptionParameters

    '
    ' create process type for creating spot tree

    Dim latticeStrategy As ILatticeStrategy: Set latticeStrategy = New CRRNoDrift
    latticeStrategy.init optionFactory.getOptionParameters
    '
    ' create iterator for traversing tree structure

    Dim latticeIterator As ITreeIterator: Set latticeIterator = New EuropeanTreeIterator
    latticeIterator.init payoff, optionFactory.getOptionParameters

    '
End Sub

As we can see, ExcelFactory is creating all option-related parameters into parameter wrapper in the first stage. Then, we create VanillaCallPayoff and feed it with parameter wrapper which is "centrally hosted" by ExcelFactory. After this, we create CRRNoDrift and use it for calculating binomial process parameters, by feeding it with parameter wrapper. Finally, we create EuropeanTreeIterator and feed it with parameter wrapper and VanillaCallPayoff function. It should be noted, that iterator has the actual Tree data structure aggregated inside it. Let us go forward.

Option Explicit
'
Sub Tester()
    '
    ' create option parameters in option factory
    Dim optionFactory As IOptionFactory: Set optionFactory = New ExcelFactory
    optionFactory.createOptionParameters
    '
    ' create option payoff object
    Dim payoff As IOneFactorPayoff: Set payoff = New VanillaCallPayoff
    payoff.init optionFactory.getOptionParameters
    '
    ' create process type for creating spot tree
    Dim latticeStrategy As ILatticeStrategy: Set latticeStrategy = New CRRNoDrift
    latticeStrategy.init optionFactory.getOptionParameters
    '
    ' create iterator for traversing tree structure
    Dim latticeIterator As ITreeIterator: Set latticeIterator = New EuropeanTreeIterator
    latticeIterator.init payoff, optionFactory.getOptionParameters
    '
    ' create solver which uses parameters and process to calculate option value
    Dim binomialSolver As New BinomialMethod
    binomialSolver.init latticeIterator
    Debug.Print binomialSolver.getPrice(2.614)
    '
End Sub

We create class called BinomialMethod for technically hosting our EuropeanIterator implementation class. This class has init method (artificial constructor) and method getPrice method, which uses iterator to perform forward iteration (create binomial tree), calculate terminal payoffs (calculate option payoffs at maturity) and perform backward iteration (discount payoffs along the tree to current date). Finally, it returns the present value of the option for its caller (Tester).

Interfaces, Classes and Tester program

All classes mentioned above, have been presented here below. You can copy-paste these into your VBA project for testing (remember to reference Microsoft Scripting Runtime library in VB editor).

Tree data structure class. Copy into VBA Class Module (Name = Tree)

Option Explicit
'
' ZERO-INDEXED data structure (array of arrays)
' example indexing access: period 2, state 1 = outer(2)(1)
Private outer() As Variant
Private dt As Double
'
Public Function init(ByVal timeInYears As Double, ByVal numberOfPeriods As Long)
    '
    ' init function serves as artificial constructor
    ' create tree structure having n periods
    dt = (timeInYears / numberOfPeriods)
    ReDim outer(0 To numberOfPeriods)
    '
    Dim i As Long
    For i = 0 To numberOfPeriods
        Dim inner() As Double
        ReDim inner(0 To i)
        outer(i) = inner
    Next i
End Function
'
Public Function push(ByVal period As Long, ByVal state As Long, ByVal value As Double)
    ' setter function
    outer(period)(state) = value
End Function
'
Public Function at(ByVal period As Long, ByVal state As Long) As Double
    ' getter function
    at = outer(period)(state)
End Function
''
Public Function n_periods() As Long
    ' return number of periods in tree structure, minus 1
    n_periods = UBound(outer, 1)
End Function
'
Public Function n_states(ByVal period As Long) As Long
    ' return number of states within a periods, minus 1
    Dim stateArray() As Double: stateArray = outer(period)
    n_states = UBound(stateArray)
End Function
'
Public Function t_at(ByVal period As Long) As Double
    ' get time in years for a node
    t_at = dt * period
End Function
'

Tree iterator interface. Copy into VBA Class Module (Name = ITreeIterator)

Option Explicit
'
Private lattice As Tree
'
Public Function forward(ByVal spot As Double)
End Function
'
Public Function backward()
End Function
'
Public Function terminalPayoff()
End Function
'
Public Function init(ByRef oneFactorPayoff As IOneFactorPayoff, ByRef parameters As Scripting.Dictionary)
End Function
'
Public Function getLattice() As Tree
End Function
'

One possible implementation for Tree iterator interface. Copy into VBA Class Module (Name = EuropeanTreeIterator)

Option Explicit
'
Implements ITreeIterator
'
Private payoff As IOneFactorPayoff
Private p As Scripting.Dictionary
Private lattice As Tree
'
Private Function ITreeIterator_forward(ByVal spot As Double)
    '
    ' get process-related parameters for filling the tree
    Dim u As Double: u = p.Item(E_UP)
    Dim d As Double: d = p.Item(E_DOWN)
    lattice.push 0, 0, spot ' initialize index (0,0) to be the user-given spot price
    '
    ' create spot tree from 0 to n
    Dim i As Long, j As Long, periods As Long
    periods = lattice.n_periods
    '
    For i = 1 To periods
        For j = 0 To (lattice.n_states(i) - 1)
            lattice.push i, j, lattice.at(i - 1, j) * d
            lattice.push i, j + 1, lattice.at(i - 1, j) * u
        Next j
    Next i
End Function
'
Private Function ITreeIterator_backward()
    '
    ' modify this - node-to-node iterating is not required (use binomial probabilities)
    ' transform spot tree to option tree from n to 0 (index 0,0 is the option value)
    ' get discount factor
    Dim df As Double: df = VBA.Exp(-p.Item(E_RATE) * (p.Item(E_TIME) / p.Item(E_PERIODS)))
    Dim w As Double: w = p.Item(E_PROBABILITY)
    Dim q As Double: q = (1 - w)
    '
    ' re-calculate option tree backwards from n to 0
    Dim i As Long, j As Long, periods As Long
    periods = lattice.n_periods
    '
    For i = periods To 0 Step -1
        For j = (lattice.n_states(i) - 1) To 0 Step -1
            '
            Dim value As Double
            value = (w * (lattice.at(i, j + 1)) + q * (lattice.at(i, j))) * df
            lattice.push i - 1, j, value
        Next j
    Next i
End Function

Private Function ITreeIterator_getLattice() As Tree
    Set ITreeIterator_getLattice = lattice
End Function

Private Function ITreeIterator_init(ByRef oneFactorPayoff As IOneFactorPayoff, _
ByRef parameters As Scripting.Dictionary)
    '
    Set payoff = oneFactorPayoff
    Set p = parameters
    Set lattice = New Tree: lattice.init p.Item(E_TIME), p.Item(E_PERIODS)
End Function
'
Private Function ITreeIterator_terminalPayoff()
    '
    ' calculate terminal payoffs for a tree at maturity
    Dim j As Long, periods As Long
    periods = lattice.n_periods
    '
    For j = (lattice.n_states(periods)) To 0 Step -1
        '
        Dim terminalValue As Double
        terminalValue = payoff.getPayoff(lattice.at(periods, j))
        lattice.push periods, j, terminalValue
    Next j
End Function
'

Lattice strategy interface. Copy into VBA Class Module (Name = ILatticeStrategy)

Option Explicit
'
Public Function init(ByRef parameters As Scripting.Dictionary)
End Function
'

One possible implementation for Lattice strategy interface. Copy into VBA Class Module (Name = CRRNoDrift)

Option Explicit
'
' this class implements Cox, Ross and Rubinstein model with no drift factor
Implements ILatticeStrategy
'
Private p As Scripting.Dictionary
'
Private Function ILatticeStrategy_init(ByRef parameters As Scripting.IDictionary)
    '
    ' init parameter dictionary
    Set p = parameters
    '
    ' calculate process-related parameters into parameters
    Dim dt As Double: dt = p.Item(E_TIME) / p.Item(E_PERIODS)
    '
    ' calculate up and down factors into parameters
    p.Item(E_UP) = VBA.Exp(p.Item(E_VOLATILITY) * VBA.Sqr(dt))
    p.Item(E_DOWN) = VBA.Exp(-p.Item(E_VOLATILITY) * VBA.Sqr(dt))
    '
    ' calculate risk-neutral probability factor into parameters
    p.Item(E_PROBABILITY) = ((VBA.Exp(p.Item(E_RATE) * dt) - p.Item(E_DOWN)) / (p.Item(E_UP) - p.Item(E_DOWN)))
End Function
'

Payoff interface. Copy into VBA Class Module (Name = IOneFactorPayoff)

Option Explicit
'
Public Function getPayoff(ByVal spot As Double) As Double
End Function
'
Public Function init(ByRef parameters As Scripting.Dictionary)
End Function
'

One possible implementation for payoff interface. Copy into VBA Class Module (Name = VanillaCallPayoff).

Option Explicit
'
' one factor vanilla call option payoff
Implements IOneFactorPayoff
'
Private x As Double
'
Private Function IOneFactorPayoff_getPayoff(ByVal spot As Double) As Double
    IOneFactorPayoff_getPayoff = maxPayoff(0, spot - x)
End Function
'
Private Function IOneFactorPayoff_init(ByRef parameters As Scripting.Dictionary)
    x = parameters.Item(E_STRIKE)
End Function
'
Private Function maxPayoff(ByVal a As Double, ByVal b As Double) As Double
    '
    maxPayoff = b
    If (a > b) Then maxPayoff = a
End Function
'

Binomial method class. Copy into VBA Class Module (Name = BinomialMethod).

Option Explicit
'
Private it As ITreeIterator 
'
Public Function init(ByRef iterator As ITreeIterator)
    '
    ' artificial constructor
    Set it = iterator
End Function
'
Public Function getPrice(ByVal spot As Double) As Double
    '
    ' this function builds tree and iterates it forward and backward to calculate option value
    it.forward spot ' create spot tree
    it.terminalPayoff ' calculate all payoffs at maturity
    it.backward ' calculate option value
    getPrice = it.getLattice.at(0, 0)
End Function
'

Interface for option factory. Copy into VBA Class Module (Name = IOptionFactory).

Option Explicit
'
Public Function createOptionParameters()
End Function
'
Public Function getOptionParameters() As Scripting.Dictionary
End Function
'

One possible implementation of option factory. Copy into VBA Class Module (Name = ExcelFactory).

Option Explicit
'
' class reads parameters data from specific excel worksheet
Implements IOptionFactory
'
Private optionParameters As Scripting.Dictionary ' data structure to hold all needed option parameters
'
Private Function IOptionFactory_createOptionParameters() As Variant
    '
    Set optionParameters = New Scripting.Dictionary
    Dim r As Range: Set r = Sheets("Sheet1").Range("D2:D6")
    '
    optionParameters.Item(E_STRIKE) = VBA.CDbl(r(1, 1))
    optionParameters.Item(E_VOLATILITY) = VBA.CDbl(r(2, 1))
    optionParameters.Item(E_TIME) = VBA.CDbl(r(3, 1))
    optionParameters.Item(E_RATE) = VBA.CDbl(r(4, 1))
    optionParameters.Item(E_PERIODS) = VBA.CLng(r(5, 1))
    '
    Set r = Nothing
    End Function
'
Private Function IOptionFactory_getOptionParameters() As Scripting.IDictionary
    Set IOptionFactory_getOptionParameters = optionParameters
End Function
'

Then we also need that Enumerator for our parameter wrapper. Copy into VBA Standard Module.

Option Explicit
'
Public Enum PRM
    '
    ' process-related parameters (calculated by ILatticeStrategy implementation)
    E_UP = 1
    E_DOWN = 2
    E_PROBABILITY = 3
    '
    ' option-related parameters (created by IOptionFactory implementation)
    E_RATE = 4
    E_STRIKE = 5
    E_VOLATILITY = 6
    E_PERIODS = 7
    E_TIME = 8
    '
End Enum
'

Program example

We create our tester program for vanilla equity call option, which is not paying any cashflows. Set the following data into Excel Worksheet. Make sure, that the range reference in ExcelFactory class is referring to this range in your Excel.

parameter value
strike 2,600
vol 42,9 %
time 0,271
rate 0,3 %
periods 250

Note, that in this design we are giving spot value to BinomialMethod object as an argument in its getPrice method. Below here is the actual tester program. Copy-paste it into VBA Standard Module.

Option Explicit
'
Sub Tester()
    '
    ' create option parameters in option factory
    Dim optionFactory As IOptionFactory: Set optionFactory = New ExcelFactory ' can be switched at runtime!
    optionFactory.createOptionParameters
    '
    ' create option payoff object
    Dim payoff As IOneFactorPayoff: Set payoff = New VanillaCallPayoff ' can be switched at runtime!
    payoff.init optionFactory.getOptionParameters
    '
    ' create process type for creating spot tree
    Dim latticeStrategy As ILatticeStrategy: Set latticeStrategy = New CRRNoDrift ' can be switched at runtime!
    latticeStrategy.init optionFactory.getOptionParameters
    '
    ' create iterator for traversing tree structure
    Dim latticeIterator As ITreeIterator: Set latticeIterator = New EuropeanTreeIterator ' can be switched at runtime!
    latticeIterator.init payoff, optionFactory.getOptionParameters
    '
    ' create solver which uses parameters and process to calculate option value
    Dim binomialSolver As New BinomialMethod
    binomialSolver.init latticeIterator
    Debug.Print binomialSolver.getPrice(2.614)
    '
    ' object releasing tasks
    Set binomialSolver = Nothing
    Set latticeIterator = Nothing
    Set latticeStrategy = Nothing
    Set payoff = Nothing
    Set optionFactory = Nothing
End Sub
'

Some afterthoughts

First of all, I got my valuation for this equity option (NOK1V FH, September 13 Call, 2.6 strike) to be approximately 0.24 today when the spot was on 2.614. I confirmed this valuation to be close enough to the market by using Bloomberg OMON<GO> function.

So, what is so great about this design after all? What is the reason, why we have to have all this complexity? When we investigate that tester program, we can realize, that the following "components" can be switched at will - meaning, that we could create a new implementation for these, without breaking our existing design:

1) the source from which we create option-related parameters (Excel, txt file, database, etc)
2) payoff function (vanilla put, digital call, etc)
3) process for creating binomial tree parameters (CRR, JR, etc)
4) iterator, which calculates payoffs from binomial tree (european, american, etc)


This example program hopefully shows, that it is possible to create very flexible and extendable designs in VBA by using Interface implementation mechanism and a couple of other tricks presented in this post (parameter wrapper). Some of the components employed in this example are also quite generic in nature. We could use Tree data structure and its iterator, when creating a program for building short-term interest rate trees, for example.

My thanks about some of the central ideas presented here belongs to Daniel Duffy for his inspiring C++ design pattern example papers and C++ book chapter on this particular topic.

Well, it is time to say goodbye again. First of all, a big hats off for you, if you really have gone through this posting. Thank You, I hope you could get a bit of some idea from it.
-Mike

No comments:

Post a Comment