Showing posts with label VBA Arrays. Show all posts
Showing posts with label VBA Arrays. Show all posts

Friday, August 15, 2014

Bootstrapping default probabilities from CDS prices in VBA

Default probabilities are needed when dealing with credit market models. This time, I wanted to present one simple algorithm for bootstrapping default probabilities from CDS market prices. Final product will be just one simple Excel/VBA worksheetfunction, which can be quickly copy-pasted and used in VBE standard module.


IMPLIED SURVIVAL PROBABILITY

Calculating implied survival probabilities from CDS prices follows the same idea, as calculating implied volatility from option price. For options, we have known market price, from which we can numerically solve the corresponding option volatility by using option pricing model. For CDS, we have known market price, from which we can solve the corresponding survival probability by using CDS pricing model. This is exactly the procedure, what this algorithm is doing. However, instead of just calculating one survival probability for a given CDS price, the algorithm is calculating all survival probabilities for a given CDS term structure. The pricing model for CDS is standard model (JP Morgan approach).

Update (9.11.2016) : This presented implementation (using simple JP Morgan CDS model) ignores the effect of premium leg accruals. The resulting bias is relatively insignificant for low CDS levels but becomes material with high CDS levels. The issue has been chewed in the paper published by Lehman Brothers Fixed Income Quantitative Credit Research (Dominic O'Kane, Stuart Turnbull). On chapter 5, there is a discussion concerning premium leg valuation and related accrual effects. There is also a suggestion available for including premium accrual into this CDS pricing model. Thanks for attentive blog visitor for outlining this issue.


FUNCTION INPUT/OUTPUT

Zero-coupon bond prices, CDS prices and recovery rate assumption are needed as market data input for calculations. VBA function survivalProbability takes market information matrix (curves) and recovery rate assumption value (recovery) as input parameters. Function then returns an array of survival probabilities. Default probabilities can then be calculated from survival probabilities.

Input market information matrix (N x 3) should contain the following data in the following order:
  • 1st row vector - maturities in years
  • 2nd row vector - zero-coupon bond prices (ex. 0.9825)
  • 3rd row vector - CDS prices as basis points (ex. 0.25 % is given as 25)

After giving required input parameters for this function and selecting correct range for function output, remember to press CTRL+SHIFT+ENTER for retrieving result array (N x 1) into worksheet.


VBA FUNCTION


Option Explicit
'
' function takes market curves matrix (Nx3) and recovery rate (1x1) as arguments, then calculates and
' returns vector of survival probabilities (Nx1) for a given market data
' matrix input data order: 1st row vector = time, 2nd row vector = zero-coupon bond prices,
' 3rd row vector = cds rates in basis points
Public Function survivalProbability(ByRef curves As Range, ByVal recovery As Double) As Variant
    '
    ' information for dimensioning arrays
    Dim nColumns As Integer: nColumns = curves.Columns.Count
    Dim nRows As Integer: nRows = curves.Rows.Count
    '
    ' create arrays for data
    Dim p() As Double: ReDim p(0 To nRows)
    Dim c() As Double: ReDim c(0 To curves.Rows.Count, 1 To curves.Columns.Count)
    '
    ' copy variant array data into new array, having 1 additional item for today
    c(0, 1) = 0: c(0, 2) = 1: c(0, 3) = 0
    Dim cInput As Variant: cInput = curves.Value2
    '
    Dim i As Integer, j As Integer, k As Integer
    For i = 1 To nRows
        c(i, 1) = cInput(i, 1)
        c(i, 2) = cInput(i, 2)
        c(i, 3) = cInput(i, 3)
    Next i
    '
    ' calculation of survival probabilities (SP)
    Dim L As Double: L = (1 - recovery)
    Dim term As Double, terms As Double, divider As Double, term1 As Double, term2 As Double
    '
    For i = LBound(p) To UBound(p)
        '
        If (i = 0) Then p(i) = 1# ' SP today is one
        If (i = 1) Then p(i) = L / ((c(i, 3) / 10000) * (c(i, 1) - c(i - 1, 1)) + L) ' first SP formula
        '
        If (i > 1) Then ' SP after first period are calculated recursively
            terms = 0
            For j = 1 To (i - 1)
                term = c(j, 2) * (L * p(j - 1) - (L + (c(j, 1) - c(j - 1, 1)) * (c(i, 3) / 10000)) * p(j))
                terms = terms + term
            Next j
            '
            divider = c(i, 2) * (L + (c(i, 1) - c(i - 1, 1)) * (c(i, 3) / 10000))
            term1 = terms / divider
            term2 = (p(i - 1) * L) / (L + (c(i, 1) - c(i - 1, 1)) * (c(i, 3) / 10000))
            p(i) = term1 + term2
        End If
    Next i
    '
    ' create output array excluding the first SP (for today)
    Dim result() As Double: ReDim result(1 To UBound(p))
    For i = 1 To UBound(p)
        result(i) = p(i)
    Next i
    '
    ' finally, transpose output array (Nx1)
    survivalProbability = Application.WorksheetFunction.Transpose(result)
End Function
'


CALCULATION EXAMPLE


The following Excel screenshot presents the calculation of default probabilities for Barclays and HSBC. Market data has been retrieved in early january 2014. VBA function input matrix (curves) has been marked with yellow color. Function output range has been marked with blue color. Default probability (PD) is calculated in column G.

















Thanks for reading.

-Mike

Sunday, January 26, 2014

Gaussian Copula implementation revisited

In my previous posting on matrix data structure, I compared the efficiency of processing matrix structures with different array data structures. The message was clear: two-dimensional arrays are the most efficient data structure when operating with large matrix operations. I have modified my implementation for Gaussian Copula in a such way, that it is using two-dimensional arrays instead of Matrix class.

Second version

The modified program is presented below. For required input data (Excel ranges), library references and external dll file, follow the instructions given on Gaussian Copula posting.

' standard VBA module (name = Enumerators)
Option Explicit
'
Public Enum E_
    P_SIMULATIONS = 1
    P_GENERATOR_TYPE = 2
    P_CORRELATION_MATRIX = 3
    P_TRANSFORM_TO_UNIFORM = 4
End Enum
'
'
'
' standard VBA module (name = MainProgram)
Option Explicit
'
Public Sub tester()
    '
    ' create correlation matrix object
    Dim correlation() As Double
    correlation = MatrixOperations.matrixFromRange(Sheets("Sheet1").Range("_correlation"))
    '
    ' create parameters for copula
    Dim parameters As New Scripting.Dictionary
    parameters.Add P_SIMULATIONS, CLng(Sheets("Sheet1").Range("_simulations").value)
    parameters.Add P_GENERATOR_TYPE, New MersenneTwister
    parameters.Add P_CORRELATION_MATRIX, correlation
    parameters.Add P_TRANSFORM_TO_UNIFORM, CBool(Sheets("Sheet1").Range("_transform").value)
    '
    ' create copula implementation
    Dim copula As ICopula: Set copula = New GaussianCopula
    copula.init parameters
    '
    ' get results from copula and write these into Excel
    Dim result() As Double: result = copula.getMatrix
    MatrixOperations.matrixToRange result, Sheets("Sheet1").Range("_dataDump")
    '
    ' release objects
    Set copula = Nothing
    Set parameters = Nothing
End Sub
'
'
'
' standard VBA module (name = MatrixOperations)
Option Explicit
'
Public Function multiplication(ByRef m1() As Double, ByRef m2() As Double) As Double()
    '
    ' get matrix multiplication
    Dim result() As Double: ReDim result(1 To UBound(m1, 1), 1 To UBound(m2, 2))
    Dim i As Long, j As Long, k As Long
    '
    Dim r1 As Long: r1 = UBound(m1, 1)
    Dim c1 As Long: c1 = UBound(m1, 2)
    Dim r2 As Long: r2 = UBound(m2, 1)
    Dim c2 As Long: c2 = UBound(m2, 2)
    Dim v As Double
    '
    For i = 1 To r1
        For j = 1 To c2
            v = 0
            '
            For k = 1 To c1
                v = v + m1(i, k) * m2(k, j)
            Next k
            result(i, j) = v
        Next j
    Next i
    multiplication = result
End Function
'
Public Function transpose(ByRef m() As Double)
    '
    ' get matrix transpose
    Dim nRows As Long: nRows = UBound(m, 1)
    Dim nCols As Long: nCols = UBound(m, 2)
    Dim result() As Double: ReDim result(1 To nCols, 1 To nRows)
    '
    Dim i As Long, j As Long
    For i = 1 To nRows
        For j = 1 To nCols
            result(j, i) = m(i, j)
        Next j
    Next i
    transpose = result
End Function
'
Public Function cholesky(ByRef c() As Double) As Double()
    '
    ' create cholesky decomposition, a lower triangular matrix
    ' d = decomposition, c = correlation matrix
    Dim s As Double
    Dim n As Long: n = UBound(c, 1)
    Dim m As Long: m = UBound(c, 2)
    Dim d() As Double: ReDim d(1 To n, 1 To m)
    '
    Dim i As Long, j As Long, k As Long
    For j = 1 To n
        s = 0
        For k = 1 To j - 1
            s = s + d(j, k) ^ 2
        Next k
        d(j, j) = (c(j, j) - s)
        If (d(j, j) <= 0) Then Exit For
        '
        d(j, j) = Sqr(d(j, j))
        '
        For i = (j + 1) To n
            s = 0
            For k = 1 To (j - 1)
                s = s + d(i, k) * d(j, k)
            Next k
            d(i, j) = (c(i, j) - s) / d(j, j)
        Next i
    Next j
    cholesky = d
End Function
'
Public Function matrixToRange(ByRef m() As Double, ByRef r As Range)
    '
    ' write matrix into Excel range
    r.Resize(UBound(m, 1), UBound(m, 2)) = m
End Function
'
Public Function matrixFromRange(ByRef r As Range) As Double()
    '
    ' read matrix from Excel range
    Dim v As Variant: v = r.Value2
    Dim r_ As Long: r_ = UBound(v, 1)
    Dim c_ As Long: c_ = UBound(v, 2)
    Dim m() As Double: ReDim m(1 To r_, 1 To c_)
    '
    ' transform variant to double
    Dim i As Long, j As Long
    For i = 1 To r_
        For j = 1 To c_
            m(i, j) = CDbl(v(i, j))
        Next j
    Next i
    matrixFromRange = m
End Function
'
'
'
' VBA class module (name = ICopula)
Option Explicit
'
' interface for copula model
'
Public Function init(ByRef parameters As Scripting.Dictionary)
    ' interface - no implementation
End Function
'
Public Function getMatrix() As Double()
    ' interface - no implementation
End Function
'
'
'
' VBA class module (name = GaussianCopula)
Option Explicit
'
Implements ICopula
'
Private n As Long ' number of simulations
Private transform As Boolean ' condition for uniform transformation
Private generator As IRandom ' random number generator implementation
'
Private c() As Double ' correlation matrix
Private d() As Double ' cholesky decomposition matrix
Private z() As Double ' independent normal random variables
Private x() As Double ' correlated normal random variables
'
Private Function ICopula_init(ByRef parameters As Scripting.Dictionary)
    '
    ' initialize class data and objects
    n = parameters(P_SIMULATIONS)
    transform = parameters(P_TRANSFORM_TO_UNIFORM)
    Set generator = parameters(P_GENERATOR_TYPE)
    c = parameters(P_CORRELATION_MATRIX)
End Function
'
Private Function ICopula_getMatrix() As Double()
    '
    ' create matrix of independent normal random numbers
    ReDim z(1 To n, 1 To UBound(c, 2))
    z = generator.getNormalRandomMatrix(UBound(z, 1), UBound(z, 2))
    '
    ' create cholesky decomposition
    d = MatrixOperations.cholesky(c)
    '
    ' create correlated normal random numbers
    z = MatrixOperations.transpose(z)
    x = MatrixOperations.multiplication(d, z)
    x = MatrixOperations.transpose(x)
    '
    ' transform correlated normal random numbers
    ' into correlated uniform random numbers
    If (transform) Then uniformTransformation
    ICopula_getMatrix = x
End Function
'
Private Function uniformTransformation()
    '
    ' map normal random number to uniform plane
    Dim nRows As Long: nRows = UBound(x, 1)
    Dim nCols As Long: nCols = UBound(x, 2)
    '
    Dim i As Long, j As Long
    For i = 1 To nRows
        For j = 1 To nCols
            x(i, j) = WorksheetFunction.NormSDist(x(i, j))
        Next j
    Next i
End Function
'
'
'
' VBA class module (name = IRandom)
Option Explicit
'
Public Function getNormalRandomMatrix( _
    ByVal nRows As Long, _
    ByVal nCols As Long) As Double()
    '
    ' interface - no implementation
    ' takes in two parameters (number of rows and columns) and
    ' returns double() filled with normal random variates
End Function
'
'
'
' VBA class module (name = MersenneTwister)
Option Explicit
'
Implements IRandom
'
Private Declare Function nextMT Lib "C:\temp\mt19937.dll" Alias "genrand" () As Double
'
Private Function IRandom_getNormalRandomMatrix( _
    ByVal nRows As Long, _
    ByVal nCols As Long) As Double()
    '
    ' retrieve NxM matrix with normal random numbers
    Dim r() As Double: ReDim r(1 To nRows, 1 To nCols)
    Dim i As Long, j As Long
    For i = 1 To nRows
        For j = 1 To nCols
            r(i, j) = InverseCumulativeNormal(nextMT())
        Next j
    Next i
    '
    IRandom_getNormalRandomMatrix = r
End Function
'
Public Function InverseCumulativeNormal(ByVal p As Double) As Double
    '
    ' Define coefficients in rational approximations
    Const a1 = -39.6968302866538
    Const a2 = 220.946098424521
    Const a3 = -275.928510446969
    Const a4 = 138.357751867269
    Const a5 = -30.6647980661472
    Const a6 = 2.50662827745924
    '
    Const b1 = -54.4760987982241
    Const b2 = 161.585836858041
    Const b3 = -155.698979859887
    Const b4 = 66.8013118877197
    Const b5 = -13.2806815528857
    '
    Const c1 = -7.78489400243029E-03
    Const c2 = -0.322396458041136
    Const c3 = -2.40075827716184
    Const c4 = -2.54973253934373
    Const c5 = 4.37466414146497
    Const c6 = 2.93816398269878
    '
    Const d1 = 7.78469570904146E-03
    Const d2 = 0.32246712907004
    Const d3 = 2.445134137143
    Const d4 = 3.75440866190742
    '
    'Define break-points
    Const p_low = 0.02425
    Const p_high = 1 - p_low
    '
    'Define work variables
    Dim q As Double, r As Double
    '
    'If argument out of bounds, raise error
    If p <= 0 Or p >= 1 Then Err.Raise 5
    '
    If p < p_low Then
        '
        'Rational approximation for lower region
        q = Sqr(-2 * Log(p))
        InverseCumulativeNormal = (((((c1 * q + c2) * q + c3) * q + c4) * q + c5) * q + c6) / _
        ((((d1 * q + d2) * q + d3) * q + d4) * q + 1)
        '
    ElseIf p <= p_high Then
        'Rational approximation for lower region
        q = p - 0.5
        r = q * q
        InverseCumulativeNormal = (((((a1 * r + a2) * r + a3) * r + a4) * r + a5) * r + a6) * q / _
        (((((b1 * r + b2) * r + b3) * r + b4) * r + b5) * r + 1)
        '
    ElseIf p < 1 Then
        'Rational approximation for upper region
        q = Sqr(-2 * Log(1 - p))
        InverseCumulativeNormal = -(((((c1 * q + c2) * q + c3) * q + c4) * q + c5) * q + c6) / _
        ((((d1 * q + d2) * q + d3) * q + d4) * q + 1)
    End If
End Function
'

Afterthoughts

In this version, Matrix class was replaced with plain two-dimensional array. Separate standard VBA module has been set to perform matrix operations (multiplication, transpose, cholesky decomposition, data input/output). Everything else is unchanged. With this small modification, we have reached reduction in processing times, when simulating correlated random numbers with Gaussian Copula model.

-Mike

Saturday, January 25, 2014

Data structure for matrix in VBA

Large part of programming financial models has something to do with handling and operating matrices. However, for handling any matrix data, there is not ready-made data structure available for this purpose in VBA. The only way to get around this limitation, is to write your own custom data structure by using existing data structures, such as arrays. Within my previous posting on Gaussian Copula implementation, I created one such custom data structure, a Matrix class. Technically speaking, this class is just wrapping arrays into a manageable object with setters and getters, plus provides some of the most common matrix operations for the user.

The idea was very noble and I was quite happy with the first development candidate. I especially liked the idea of data structure being an object, also for schematic and semantic reasons. Plus, I thought that I would finally get rid of all those boring extra lines of code needed, when using plain arrays. I also thought that only a small performance penalty would be paid, with all function calls made using class accessors (push, at). However, as I was prototyping Monte Carlo basket equity option pricing and doing matrix operations with large matrices, I quickly realized that the cost of processing matrix operations was definitely way too high.

Testing processing times

The issue was bothering me in a such way, that I finally wanted to get some hard-tested facts on handling and operating matrix structures. For this reason, I prepared test cases for three different matrix schemes. Within these test cases, matrix data structure was implemented by using
  1. Two-dimensional array
  2. Variant array of double arrays (jagged array)
  3. Matrix class
The use of Collection and Dictionary data structures has been left out of this experiment completely, since these data structures are empirically known to be more costly than the use of arrays. Nick Webber has been doing some serious woodshedding with these issues in his excellent book Implementing Models of Financial Derivatives: Object Oriented Applications with VBA within the chapter 16.

Within test cases mentioned, a simple procedural program performs the following operations for all matrix schemes described above
  1. Creates three matrices (A, B, C)
  2. Fills two matrices (A, B) with random numbers
  3. Performs matrix multiplication (A, B) and returns the result into matrix (C)
Time elapsed was recorded only for the actual matrix multiplication operation. For each matrix schemes, matrix B rows (A columns) were dimensioned from 100 000  to 2 000 000 and matrix B columns (A rows) were assumed to be constant 10. For example, in the first calculation, we multiplied matrix A (10 * 100 000) with matrix B (100 000 * 10) and received matrix C (10 * 10). In the second calculation matrix dimensions were A (10 * 200 000) and B (200 000 * 10) and we received matrix C (10 * 10), and so on.

Cold shower

The following chart is presenting the findings of this experiment.



We can clearly see, that a simple two-dimensional array is the most efficient data structure for handling large matrix operations in VBA. There is just no way out of this, period. Testing program is presented below. You can just copy-paste it into a new standard VBA module, if you are interested to run it in your own laptop. Remember to create reference to Microsoft Scripting Runtime library.

Option Explicit
'
Private Declare Function GetTickCount Lib "kernel32.dll" () As Long
Private Const filePath As String = "C:\temp\matrix_log.txt"
Private fileSystem As Scripting.FileSystemObject
Private textWriter As TextStream
Private textWriterEnabled As Boolean
Private stream As String
Private startTime As Long
Private endTime As Long
Private timeElapsed As Double
'
Sub tester()
    '
    Set fileSystem = New Scripting.FileSystemObject
    Set textWriter = fileSystem.OpenTextFile(filePath, ForWriting, True)
    textWriterEnabled = True
    '
    Dim r As Long: r = 100000
    Dim c As Long: c = 10
    Dim i As Long
    For i = 0 To 19
        testRun_2DArray r + i * r, c
        testRun_arrayOfArrays r + i * r, c
        testRun_matrixClass r + i * r, c
    Next i
    '
    MsgBox "completed", vbInformation, "timer log file for matrix operations"
    Set textWriter = Nothing
    Set fileSystem = Nothing
End Sub
'
Private Function testRun_2DArray(ByVal r As Long, ByVal c As Long)
    '
    ' create 2-dim arrays needed
    Dim m1() As Double: ReDim m1(1 To r, 1 To c)
    Dim m2() As Double: ReDim m2(1 To c, 1 To r)
    Dim m3() As Double: ReDim m3(1 To c, 1 To c)
    Dim i As Long, j As Long, k As Long
    '
    ' fill array 1
    For i = 1 To r
        For j = 1 To c
            m1(i, j) = Rnd
        Next j
    Next i
    '
    ' fill array 2
    For i = 1 To r
        For j = 1 To c
            m2(j, i) = Rnd
        Next j
    Next i
    '
    ' perform matrix multiplication
    startTime = GetTickCount()
    Dim v As Double
    '
    For i = 1 To c
        For j = 1 To c
            v = 0
            '
            For k = 1 To r
                v = v + m2(i, k) * m1(k, j)
            Next k
            m3(i, j) = v
        Next j
    Next i
    '
    ' write timer results into log file
    endTime = GetTickCount()
    timeElapsed = (endTime - startTime) / 1000
    stream = "testRun_2DArray;" & r & ";" & timeElapsed
    If (textWriterEnabled) Then textWriter.WriteLine stream
End Function
'
Private Function testRun_arrayOfArrays(ByVal r As Long, ByVal c As Long)
    '
    ' create arrays of arrays needed
    Dim i As Long, j As Long, k As Long
    Dim inner() As Double
    '
    Dim m1() As Variant: ReDim m1(1 To r)
    For i = 1 To r
        ReDim inner(1 To c)
        m1(i) = inner
    Next i
    '
    Dim m2() As Variant: ReDim m2(1 To c)
    For i = 1 To c
        ReDim inner(1 To r)
        m2(i) = inner
    Next i
    '
    Dim m3() As Variant: ReDim m3(1 To c)
    For i = 1 To c
        ReDim inner(1 To c)
        m3(i) = inner
    Next i
    '
    ' fill array 1
    For i = 1 To r
        For j = 1 To c
            m1(i)(j) = Rnd
        Next j
    Next i
    '
    ' fill array 2
    For i = 1 To r
        For j = 1 To c
            m2(j)(i) = Rnd
        Next j
    Next i
    '
    ' perform matrix multiplication
    startTime = GetTickCount()
    Dim v As Double
    '
    For i = 1 To c
        For j = 1 To c
            v = 0
            '
            For k = 1 To r
                v = v + m2(i)(k) * m1(k)(j)
            Next k
            m3(i)(j) = v
        Next j
    Next i
    '
    ' write timer results into log file
    endTime = GetTickCount()
    timeElapsed = (endTime - startTime) / 1000
    stream = "testRun_arrayOfArrays;" & r & ";" & timeElapsed
    If (textWriterEnabled) Then textWriter.WriteLine stream
End Function
'
Private Function testRun_matrixClass(ByVal r As Long, ByVal c As Long)
    '
    ' create 2 matrix objects
    Dim m1 As New Matrix: m1.init r, c
    Dim m2 As New Matrix: m2.init c, r
    Dim i As Long, j As Long
    '
    ' fill matrix 1
    For i = 1 To r
        For j = 1 To c
            m1.push i, j, Rnd
        Next j
    Next i
    '
    ' fill matrix 2
    For i = 1 To c
        For j = 1 To r
            m2.push i, j, Rnd
        Next j
    Next i
    '
    ' perform matrix multiplication
    Dim m3 As New Matrix
    startTime = GetTickCount()
    Set m3 = m3.multiplication(m2, m1)
    '
    ' write timer results into log file
    endTime = GetTickCount()
    timeElapsed = (endTime - startTime) / 1000
    stream = "testRun_matrixClass;" & r & ";" & timeElapsed
    If (textWriterEnabled) Then textWriter.WriteLine stream
    '
    Set m3 = Nothing
    Set m2 = Nothing
    Set m1 = Nothing
End Function
'

Small matrices

Additionally, I also tested using MMULT function with simple two-dimensional arrays. Efficiency of this method is only marginally better, than using two-dimensional arrays with the code provided above (testRun_2DArray). Moreover, there is a limit of the sizes of matrices what we can feed for this worksheet function and those are surprisingly low. For example, trying to multiply A (10 * 100 000) with B (100 000 * 10) leads to runtime error.

The chart below is presenting the results for test cases with small matrices, including test case for using MMULT worksheet function. For each matrix schemes, matrix B rows (A columns) were dimensioned from 1 000  to 65 000 and matrix B columns (A rows) were assumed to be constant 10. For example, in the first calculation, we multiplied matrix A (10 * 1 000) with matrix B (1 000 * 10) and received matrix C (10 * 10). In the second calculation matrix dimensions were A (10 * 2 000) and B (2 000 * 10) and we received matrix C (10 * 10), and so on.



The direction of the results is the same as with large matrices. Using MMULT worksheet function is the most efficient choice, but only marginally better than using simple two-dimensional arrays. The use of Matrix wrapper class for small matrix operations can still be seen as reasonable choice, since the time loss compared to more efficient choices is after all, relatively small.

Final run

Just for the curious, I wanted to compare VBA matrix operations efficiency results with the corresponding C++ results. For this reason, I used dynamically allocated arrays. Otherwise, the actual testing program was basically the same as for VBA cases: allocate memory for arrays, fill arrays with random numbers, perform matrix multiplication and finally release the allocated memory. Time elapsed was recorded only for the actual matrix multiplication operation. The chart below is presenting the results.



In a nutshell, average efficiency ratio (VBA processing time / C++ processing time) is 5.24 for this experiment sample. Moreover, larger arrays can be handled in C++ than in VBA, since the memory is allocated from the heap memory instead of stack memory.

Afterthoughts

So, for any large and time-critical matrix operations performed in VBA, a simple two-dimensional array is the most efficient data structure which can be provided by VBA. For a small matrix operations, arrays wrapped in class can still be used. For real hardcore calculations (very large matrices, fast processing times), VBA is unfortunately not efficient tool for handling such calculations.

Life goes on - have a great weekend!

-Mike