Anda di halaman 1dari 44

Sheet1

Bond Details Name Currency Nominal Amount Issue Date Maturity Date Coupon Rate Coupon Frequency XYZ USD 1000000 1/1/2000 12/31/2040 0.065 2

Outstanding Term (yrs) Outstanding Term (m) Outstanding Coupon Pmts Outstanding Coupon Amount

30 365

Sheet1 Option Explicit Dim firstBond As bond Private Sub cmdCreateBond_Click()

Set firstBond = New bond

With ActiveSheet

firstBond.Name = .Cells(4, 2).Value firstBond.NominalAmount = .Cells(6, 2).Value firstBond.MonetaryUnit = .Cells(5, 2).Value firstBond.DateOfIssue = CDate(.Cells(7, 2).Value) firstBond.DateOfMaturity = CDate(.Cells(8, 2).Value) firstBond.CouponRate = CDate(.Cells(9, 2).Value) firstBond.CouponFreq = CDate(.Cells(10, 2).Value)

.Cells(14, 2).Value = firstBond.OutstandingTermInYears .Cells(15, 2).Value = firstBond.OutstandingTermInMonths

End With

End Sub

Private Sub CommandButton1_Click() Dim couponDate As Date couponDate = firstBond.NextCouponPayingDate End Sub

Sheet3
Bond Portfolio Redemption Date Nominal Value Coupon Rate Redemption Yield Value of bond 1/1/2020 1000 0.07 0.075 1/2/2045 10000 0.08 0.075 1/2/2045 10000 0.08 0.075 1/2/2045 10000 0.08 0.075

Bond Portfolio

Equity Portfolio Name Nominal Value Dividend Yield Expected Return Dividend growth rate Dividend Growth Period Value of stock

ABC Bhd 2000 0.025 0.12 0.05 800.0000 10840.031

DEF Bhd 2000 0.025 0.12 0.05 5 558.6012

DEF Bhd 2000 0.025 0.12 0.05 10 625.1798

DEF Bhd 5000 0.065 0.09 0.05 8856.2500

Equity Portfolio

Trapazoidal Rule Acuurate a b n

41.6666675000 41.6666666667 0 5 5000

0.00000002
Trapazoidal Rule

Calculate Std Normal Prob z Pr(Z<z) n Calculate Normal Prob x Pr(X<x)

20 38

DeltaX

0.1
Calculate Std Normal Prob

14 0.96395

DeltaX Mu Sigma

0.1 10 5

Calculate Normal Prob

Calcutate Inverse Normal Pr(X<x) x Computer

0.9999999 3.72400 5.19900

DeltaX

0.00001
Calculate Inverse

Sheet3 Option Explicit Dim BondPortfolio As New Collection Dim EquityPortfolio As New Collection

Private Function NoOfInstrumentInPortfolio(startCol As Integer, startRow As Integer) As Integer Dim finished As Boolean, j As Integer

Do While Not finished If Trim$(ActiveSheet.Cells(startRow, startCol + j).Value) <> "" Then j=j+1 Else finished = True End If Loop

NoOfInstrumentInPortfolio = j End Function

Private Sub cmdEquityPortfolio_Click() Dim i As Integer, ValOfStock As Double Dim myEquity As Equity, num As Integer

num = NoOfInstrumentInPortfolio(2, 14) Set EquityPortfolio = New Collection

With ActiveSheet For i = 1 To num

Set myEquity = New Equity myEquity.NominalValue = Val(.Cells(15, i + 1).Value) myEquity.DividendYield = Val(.Cells(16, i + 1).Value) myEquity.ExpectedReturn = Val(.Cells(17, i + 1).Value) myEquity.DivGrowthRate = Val(.Cells(18, i + 1).Value) myEquity.DivGrowthPeriod = Val(.Cells(19, i + 1).Value) EquityPortfolio.Add myEquity Set myEquity = Nothing Next i i=1

Dim equityType As Equity Dim totEquityValue As Double For Each equityType In EquityPortfolio ValOfStock = equityType.EquityValue totEquityValue = totEquityValue + ValOfStock .Cells(20, i + 1).Value = Format$(ValOfStock, "0.0000") i=i+1 Next equityType .Cells(22, 2).Value = Format$(totEquityValue, "0.0000") End With End Sub

Private Sub cmdPortfolio_Click() Dim i As Integer, marketValue As Double, redYield As Double Dim mybond As bond, ValOfStock As Double, num As Integer

num = NoOfInstrumentInPortfolio(2, 4)

Set BondPortfolio = New Collection

With ActiveSheet For i = 1 To 2 Set mybond = New bond mybond.RedemptionDate = CDate(.Cells(3, i + 1).Value) mybond.NominalAmount = Val(.Cells(4, i + 1).Value) mybond.CouponRate = Val(.Cells(5, i + 1).Value) BondPortfolio.Add mybond Set mybond = Nothing Next i redYield = Val(.Cells(6, 2).Value) Dim bondtype As bond For Each bondtype In BondPortfolio marketValue = marketValue + bondtype.BondValue(redYield) / 100 * bondtype.NominalAmount Next bondtype

BondPortfolio.Remove 1

For Each bondtype In BondPortfolio marketValue = marketValue + bondtype.BondValue(redYield) / 100 * bondtype.NominalAmount Next bondtype i=0 For Each bondtype In BondPortfolio i=i+1 If bondtype.RedemptionDate = CDate("1/2/2045") Then BondPortfolio.Remove i Exit For

End If Next bondtype

'bond portfolio.remove 2 ' For i = 1 To BondPortfolio.Count ' BondPortfolio.Remove 1 'Next i

End With End Sub

Private Sub cmdTrapazoidalRule_Click() Dim TrapRule As NormalDistribution, a As Double, b As Double, n As Integer Set TrapRule = New NormalDistribution Dim results() As Double

With ActiveSheet a = Val(.Cells(27, 2).Value) b = Val(.Cells(28, 2).Value) n = Val(.Cells(29, 2).Value) results = TrapRule.ImplementTrapazoidalRule(a, b, n) .Cells(25, 2).Value = Format$(results(0), "0.0000000000") .Cells(26, 2).Value = Format$(results(1), "0.0000000000") .Cells(26, 3).Value = Format$(results(2), "0.0000000000") End With End Sub

Private Sub cmdNormalProb_Click()

Dim nd As NormalDistribution Dim z As Double, deltaX As Double Dim res As Double

Set nd = New NormalDistribution With ActiveSheet z = Val(.Cells(33, 2).Value) deltaX = Val(.Cells(33, 4).Value)

.Cells(34, 2).Value = Format$(nd.PrZ(z, deltaX), "0.00000") End With End Sub

Private Sub cmdCalNormalProb_Click() Dim nd As NormalDistribution Dim X As Double, deltaX As Double Dim res As Double, variance As Double

Set nd = New NormalDistribution With ActiveSheet X = Val(.Cells(38, 2).Value) deltaX = Val(.Cells(38, 4).Value) nd.mu = Val(.Cells(39, 4).Value) variance = Val(.Cells(40, 4).Value) nd.Sigma = variance ^ 0.5 res = nd.NormalProb(X, deltaX) .Cells(39, 2).Value = Format$(res, "0.00000") End With

End Sub

Private Sub cmdCalculateInverse_Click() Dim prob As Double, z As Double, z1 As Double Dim norm As NormalDistribution, deltaX As Double Set norm = New NormalDistribution

With ActiveSheet deltaX = Val(.Cells(43, 4).Value) prob = Val(.Cells(43, 2).Value) z = norm.Inverse(prob, 0, 1, 0.001) .Cells(44, 2).Value = Format$(z, "0.000") z1 = Application.WorksheetFunction.NormInv(prob, 0, 1) .Cells(45, 2).Value = Format$(z1, "0.000") End With End Sub

Sheet4
Mean Random Numbers 0.407827 0.949413 0.138071 0.06935 0.971251 0.615829 0.318753 0.237508 0.586163 0.662941 0.751881 0.464737 0.574643 Value Error 0.500247 0.000495 Variance 0.08329 0.00052

Generate Random Numbers

Generate Normal RV

Mean Variance Prob Normal Inverse

100 100 0.00886 -137.143 -47.7915

Get Normal Inverse

Sheet4 Option Explicit

Private Sub cmdGenerateRandomNumbers_Click() Dim i%, randArray() As Double, mean As Double, variance As Double Dim sum As Double, sumSq As Double, errMean As Double, errVar As Double

Const n = 2999

With ActiveSheet ReDim randArray(n) For i = 0 To n randArray(i) = Rnd Next i

For i = 0 To n .Cells(2 + i, 2).Value = Format$(randArray(i), "0.000000") sum = sum + randArray(i) sumSq = sumSq + randArray(i) * randArray(i) Next i

mean = sum / (n + 1) variance = sumSq / (n + 1) - mean * mean .Cells(2, 5).Value = Format$(mean, "0.000000") .Cells(2, 6).Value = Format$(variance, "0.000000") errMean = Abs((mean - 0.5) / 0.5) errVar = Abs((variance - 1 / 12) * 12) .Cells(3, 5).Value = Format$(errMean, "0.000000")

.Cells(3, 6).Value = Format$(errVar, "0.000000") End With End Sub

Private Sub cmdGenerateNormRV_Click()

End Sub

Private Sub cmdGetNormInv_Click() Dim mean As Double, variance As Double, prob As Double Dim inverseNormal As Double, i%

With ActiveSheet mean = Val(.Cells(10, 5).Value) variance = Val(.Cells(11, 5).Value) prob = Rnd .Cells(12, 5).Value = Format$(prob, "0.000000") inverseNormal = Application.WorksheetFunction.NormInv(prob, mean, variance) .Cells(13, 5).Value = Format$(inverseNormal, "0.000000") For i = 0 To 199 prob = Rnd inverseNormal = Application.WorksheetFunction.NormInv(prob, mean, variance) .Cells(14 + i, 5).Value = Format$(inverseNormal, "0.000000") Next i End With End Sub

Sheet5
Stock ABC Bhd Lower 0.00001 Upper 100 Probabilit y 0.8898 0.8898

Expexted Returns Mean 0.05 Varianc e 0.7 No. of Periods Current Price 20 100

Stock

Stock Price Less Than Upper Limit Lowest 19 59.787

0.8908 Highest 15 222.485

Returns/Price Simulator Retur Period Price n 1 108.85 96.371 2 1 0.1218 147.85 3 1 0.428 63.999 4 3 0.8373 97.820 5 2 0.4243 116.80 6 6 0.1774 185.17 7 4 0.4608 116.41 8 6 0.4641

Period Value

Simulate

Get Probability Pr [Stock < Upper Limit]

Sheet5 Option Explicit

Private Sub cmdSimulator_Click() 'Price Dim mean As Double, variance As Double, p0 As Double, p1 As Double, R As Double Dim period As Integer, i As Integer Dim nd As NormalDistribution Set nd = New NormalDistribution 'Return Dim Pt As Double, Pt_1 As Double, r1 As Double, j As Integer, finished As Boolean 'Period Dim no As Double, h As Integer, K As Integer 'Highest & Lowest Prices Dim min As Double, max As Double, minPeriod As String, maxPeriod As String Dim finished1 As Boolean, m As Integer, price As Double min = 1000000 max = 0

With ActiveSheet

'Calculate Price mean = Val(.Cells(4, 2).Value) variance = Val(.Cells(5, 2).Value) period = Val(.Cells(7, 3).Value) nd.mean = mean nd.variance = variance p0 = Val(.Cells(8, 3).Value)

For i = 1 To period p1 = nd.SimulateStockPrice(p0) .Cells(11 + i, 2).Value = Format$(p1, "0.00000") 'P0 = p1 Next i

'Calculate Return Pt_1 = Val(.Cells(12, 2).Value) j=1 Do While Not finished If .Cells(12 + j, 2).Value <> "" Then Pt = Val(.Cells(12 + j, 2).Value) r1 = Log(Pt) - Log(Pt_1) j=j+1 .Cells(11 + j, 3).Value = Format$(r1, "0.0000") Pt_1 = Pt Else finished = True End If Loop

'List the Period no = Val(.Cells(7, 3).Value) For h = 1 To no .Cells(11 + h, 1).Value = Format$(h, "0.000") Next h h=h+1

'Find Highest & Lowest Prices Do While Not finished1 If Trim(.Cells(12 + m, 2).Value) <> "" Then price = Val(.Cells(12 + m, 2).Value) If price < min Then min = price minPeriod = .Cells(12 + m, 1).Value End If

If price > max Then max = price maxPeriod = .Cells(12 + m, 1).Value End If

m=m+1 Else finished1 = True End If Loop .Cells(10, 6).Value = Format$(min, "0.000") .Cells(10, 7).Value = Format$(max, "0.000") .Cells(9, 6).Value = minPeriod .Cells(9, 7).Value = maxPeriod End With End Sub Private Sub cmdGetProbability_Click() Dim mean As Double, variance As Double, p0 As Double, period As Integer Dim nd As NormalDistribution, p As Double, a As Double, b As Double, i As Integer

Dim results() As Double Set nd = New NormalDistribution

With ActiveSheet mean = Val(.Cells(4, 2).Value) variance = Val(.Cells(5, 2).Value) period = Val(.Cells(7, 3).Value) a = Val(.Cells(3, 5).Value) b = Val(.Cells(3, 6).Value) p0 = Val(.Cells(8, 2).Value) nd.mean = mean nd.variance = variance results = nd.ProbLogNormal(a, b, period) .Cells(3, 7).Value = Format$(results(0), "0.0000") .Cells(4, 7).Value = Format$(results(1), "0.0000") End With End Sub

Private Sub cmdProbLessThanUpperLimit_Click() Dim mean As Double, variance As Double, p0 As Double, period As Integer Dim nd As NormalDistribution, p As Double, a As Double, b As Double, prob As Double Dim results() As Double Set nd = New NormalDistribution

With ActiveSheet mean = Val(.Cells(4, 2).Value) variance = Val(.Cells(5, 2).Value) period = Val(.Cells(7, 3).Value)

a = Val(.Cells(3, 5).Value) b = Val(.Cells(3, 6).Value) p0 = Val(.Cells(8, 3).Value) nd.mean = mean nd.variance = variance prob = nd.LogNormal(b, period) .Cells(6, 7).Value = Format$(prob, "0.0000") End With End Sub

Sheet6
Exotic Option Option Type Underlying Price Strike Price Expiry Period (M) Call-Average Arithmetic Average 100 3

Underlying Current Price Returns Distribution Normal Mean Variance

100 0.05 0.16


Value Option

no of Simulation 0 50542.0765

789

highest no.of simulation=16383

Total payoff

Option Price

32.0292

Sheet6 Option Explicit

Private Sub cmdGetPricesForExoticOption_Click() Dim mean As Double, variance As Double, totalPayoff As Double Dim noOfSimulation As Integer, i As Integer, j As Integer Dim p1() As Double, payoff() As Double, optionPrice As Double

Dim nd As NormalDistribution Set nd = New NormalDistribution Dim eo As ExoticOption Set eo = New ExoticOption

With ActiveSheet eo.optionType = .Cells(3, 2).Value eo.strikePrice = Val(.Cells(5, 2).Value) eo.expiryPeriod = Val(.Cells(6, 2).Value) eo.currentStockPrice = Val(.Cells(10, 2).Value) mean = Val(.Cells(12, 2).Value) variance = Val(.Cells(13, 2).Value) noOfSimulation = Val(.Cells(15, 2).Value)

nd.mean = mean nd.variance = variance

For i = 1 To noOfSimulation p1 = eo.GetAssetPrices(mean, variance) payoff = eo.GetOptionPayoff(p1)

For j = 0 To 1 totalPayoff = totalPayoff + payoff(j) .Cells(17, 2).Value = Format$(payoff(j), "0.0000") .Cells(18, 2).Value = Format$(totalPayoff, "0.0000") Next j Next i optionPrice = totalPayoff / (2 * noOfSimulation) .Cells(21, 2).Value = Format$(optionPrice, "0.0000") End With End Sub

Class Module Dept. Bond Option Explicit

Private fName As String Private fNominalAmount As Double Private fMonetaryUnit As String Private fDateOfIssue As Date Private fDateOfMaturity As Date Private fCouponRate As Double Private fCouponFreq As Integer Private fRedemptionDate As Date Private fComputation As Double Private fPrice As Double Public Property Get price() As Double price = fPrice End Property Public Property Let price(ByRef v As Double) fPrice = v End Property Public Property Get Name() As String Name = fName End Property Public Property Let Name(ByRef v As String) fName = v End Property

Public Property Get NominalAmount() As Double

NominalAmount = fNominalAmount End Property

Public Property Let NominalAmount(ByRef v As Double) fNominalAmount = v End Property

Public Property Get MonetaryUnit() As String MonetaryUnit = fMonetaryUnit End Property Public Property Let MonetaryUnit(ByRef v As String) fMonetaryUnit = v End Property

Public Property Get DateOfIssue() As Date DateOfIssue = fDateOfIssue End Property Public Property Let DateOfIssue(ByRef v As Date) fDateOfIssue = v End Property

Public Property Get DateOfMaturity() As Date DateOfMaturity = fDateOfMaturity End Property Public Property Let DateOfMaturity(ByRef v As Date) fDateOfMaturity = v End Property Public Function OutstandingTermInYears() As Integer

Dim term As Integer term = DateDiff("yyyy", CDate(Now), fDateOfMaturity) OutstandingTermInYears = term End Function Public Function OutstandingTermInMonths() As Integer Dim term As Integer term = DateDiff("m", CDate(Now), fDateOfMaturity) OutstandingTermInMonths = term End Function Public Property Get CouponRate() As Double CouponRate = fCouponRate End Property Public Property Let CouponRate(ByRef v As Double) fCouponRate = v End Property Public Property Get CouponFreq() As Integer CouponFreq = fCouponFreq End Property Public Property Let CouponFreq(ByRef v As Integer) fCouponFreq = v End Property Public Function NextCouponPayingDate() As Date Dim tstDate As Date, K As Integer

testDate = fDateOfIssue K=1 Do While testDate < CDate(Now)

testDate = DateAdd("m", 6 * K, fDateOfIssue) K=K+1

Loop NextCouponPayingDate = testDate End Function Public Property Get RedemptionDate() As Date RedemptionDate = fRedemptionDate End Property Public Property Let RedemptionDate(ByRef v As Date) fRedemptionDate = v End Property Public Property Get Computation() As Double Computation = fComputation End Property Public Property Let Computation(ByRef v As Double) fComputation = v End Property Public Function AddDate(noofMonths As Integer) As Date AddDate = DateAdd("m", noofMonths, fRedemptionDate) End Function Public Function GetRedemptionYield(p As Double, epsilon As Double, a As Double, b As Double) As Double Dim f As Double, n As Integer, found As Boolean, c As Double Dim fa As Double, fb As Double, fc As Double n = GetOutstandingTerm

Do While Not found

c = (a + b) / 2 fc = Fi(p, c, n) If Abs(fc) < epsilon Then found = True Else

fa = Fi(p, a, n) fb = Fi(p, b, n) If fa * fc < 0 Then b=c

Else

a=c

End If

End If

Loop

GetRedemptionYield = c

End Function Private Function Fi(p As Double, i As Double, n As Integer) As Double

Fi = fCouponRate * 100 / i * (1 - 1 / (1 + i) ^ n) + 100 * 1 / (1 + i) ^ n - p

End Function Private Function GetOutstandingTerm() As Integer Dim n As Integer

n = DateDiff("yyyy", CDate(Now), fRedemptionDate) GetOutstandingTerm = n

End Function Public Function BondValue(i As Double) As Double Dim n As Integer n = GetOutstandingTerm BondValue = fCouponRate * 100 / i * (1 - 1 / (1 + i) ^ n) + 100 * 1 / (1 + i) ^ n

End Function Private Sub Class_Initialize() End Sub

Equity Option Explicit

Private fName As String Private fNominalValue As Double Private fDividendYield As Double Private fDivGrowthRate As Double Private fMarketValue As Double Private fExpectedReturn As Double Private fMarketShare As Double Private fAnnualDividend As Double Private fDivGrowthPeriod As Integer

Public Property Get DivGrowthPeriod() As Integer

DivGrowthPeriod = fDivGrowthPeriod

End Property Public Property Let DivGrowthPeriod(ByRef v As Integer)

fDivGrowthPeriod = v

End Property

Public Property Get AnnualDividend() As Double

AnnualDividend = fAnnualDividend

End Property Public Property Let AnnualDividend(ByRef v As Double)

fAnnualDividend = v

End Property Public Property Get MarketShare() As Double

MarketShare = fMarketShare

End Property Public Property Let MarketShare(ByRef v As Double)

fMarketShare = v

End Property

Public Property Get ExpectedReturn() As Double

ExpectedReturn = fExpectedReturn

End Property Public Property Let ExpectedReturn(ByRef v As Double)

fExpectedReturn = v

End Property

Public Property Get Name() As String

Name = fName

End Property Public Property Let Name(ByRef v As String)

fName = v

End Property Public Property Get NominalValue() As Double

NominalValue = fNominalValue

End Property Public Property Let NominalValue(ByRef v As Double)

fNominalValue = v

End Property Public Property Get DividendYield() As Double

DividendYield = fDividendYield

End Property Public Property Let DividendYield(ByRef v As Double)

fDividendYield = v

End Property Public Property Get DivGrowthRate() As Double

DivGrowthRate = fDivGrowthRate

End Property Public Property Let DivGrowthRate(ByRef v As Double)

fDivGrowthRate = v

End Property Public Function ObtainValue(discountRate As Double) As Double ObtainValue = fDividendYield / discountRate End Function Public Function ObtainExpectedReturns(price As Double) As Double ObtainExpectedReturns = price / fDividendYield End Function

Public Function EquityValue() As Double

Dim i As Double

If fDivGrowthPeriod = 0 Then i = (fExpectedReturn - fDivGrowthRate) / (1 + fDivGrowthRate) EquityValue = fNominalValue * fDividendYield * (1 + i) / i Else

EquityValue = EquityValueFiniteDividendGrowth End If

End Function

Private Function EquityValueFiniteDividendGrowth() As Double Dim i As Integer, sum As Double, df As Double, df2 As Double, df3 As Double df = 1 / (1 + (fExpectedReturn - fDivGrowthRate) / (1 + fDivGrowthRate)) For i = 0 To fDivGrowthPeriod - 1 sum = sum + df ^ i Next i df2 = (1 + fDivGrowthRate) / (1 + fExpectedReturn) df3 = (1 + fExpectedReturn) / fExpectedReturn sum = sum + (df2 ^ fDivGrowthPeriod) * df3 EquityValueFiniteDividendGrowth = sum * fNominalValue * fDividendYield End Function

Exotic Option Option Explicit Private fnormDist As Double Private fexpiryDate As Date Private fexpiryPeriod As Integer Private fstrikePrice As Double Private foptionType As String Private fcurrentStockPrice As Double

Public Property Set normDist(ByRef v As NormalDistribution) Set fnormDist = v End Property

Public Property Let expiryDate(ByRef v As Date) fexpiryDate = v End Property

Public Property Let expiryPeriod(ByRef v As Integer) fexpiryPeriod = v End Property

Public Property Let strikePrice(ByRef v As Double) fstrikePrice = v End Property

Public Property Let optionType(ByRef v As String) foptionType = v

End Property

Public Property Let currentStockPrice(ByRef v As Double) fcurrentStockPrice = v End Property

Public Function GetOptionPayoff(assetPrice() As Double) As Double() Dim i As Integer, j As Integer Dim averagePrices() As Double ReDim averagePrices(1) Dim totPrice() As Double ReDim totPrice(1) Dim payoff() As Double ReDim payoff(1)

If Trim$(foptionType) = "Call-Average" Then For j = 0 To 1 For i = 0 To UBound(assetPrice, 2) '2-Dimensional Array totPrice(j) = totPrice(j) + assetPrice(j, i) Next i Next j

For j = 0 To 1 averagePrices(j) = totPrice(j) / ((UBound(assetPrice, 2)) + 1) If averagePrices(j) > fstrikePrice Then payoff(j) = averagePrices(j) - fstrikePrice End If

Next j GetOptionPayoff = payoff End If End Function

Public Function GetAssetPrices(mu As Double, sigmaSq As Double) As Double() Dim normDist As NormalDistribution Set normDist = New NormalDistribution Dim i As Integer, j As Integer Dim results() As Double Dim assetPrices() As Double ReDim assetPrices(0 To 1, fexpiryPeriod - 1) Dim returns() As Double ReDim returns(0 To 1, fexpiryPeriod - 1)

normDist.mu = mu normDist.variance = sigmaSq

For i = 0 To fexpiryPeriod - 1 results() = normDist.BoxMuller 'Box-Muller give two RV returns(0, i) = results(0) returns(1, i) = results(1) Next i

For j = 0 To 1 For i = 0 To fexpiryPeriod - 1 If i = 0 Then assetPrices(j, i) = fcurrentStockPrice * Exp(returns(j, i))

Else assetPrices(j, i) = assetPrices(j, i - 1) * Exp(returns(j, i)) End If Next i Next j

GetAssetPrices = assetPrices End Function

Normal Distribution Option Explicit Private fMu As Double Private fSigma As Double Private fMean As Double Private fVariance As Double

Public Property Get mu() As Double mu = fMu End Property Public Property Let mu(ByRef v As Double) fMu = v End Property

Public Property Get Sigma() As Double Sigma = fSigma End Property Public Property Let Sigma(ByRef v As Double) fSigma = v End Property

Public Property Get mean() As Double mean = fMean End Property Public Property Let mean(ByRef v As Double) fMean = v End Property

Public Property Get variance() As Double variance = fVariance End Property Public Property Let variance(ByRef v As Double) fVariance = v fSigma = fVariance ^ 0.5 End Property

Public Function ImplementTrapazoidalRule(a As Double, b As Double, n As Integer) As Double() Dim sum As Double, sum2 As Double, K As Integer, delta As Double Dim result() As Double

ReDim result(2)

delta = (b - a) / n

For K = 1 To n - 1 sum = sum + (a + K * delta) ^ 2 Next K

sum = sum + 0.5 * a ^ 2 + 0.5 * b ^ 2 sum = sum * delta sum2 = (b ^ 3 - a ^ 3) / 3

result(0) = sum result(1) = sum2 result(2) = (sum - sum2) / sum2 ImplementTrapazoidalRule = result

End Function

Private Function NormalX(X As Double) As Double Const Pi = 3.1416 NormalX = (1 / ((2 * Pi) ^ 0.5)) * (Exp(-0.5 * (X ^ 2))) End Function

Public Function PrZ(z As Double, deltaX As Double) As Double() Dim oldX As Double, newX As Double, sum As Double, tempZ As Double Dim fOldX As Double, fNewX As Double, finished As Boolean, n As Integer

Dim results() As Double ReDim results(1)

If z > 0 Then tempZ = -z Else tempZ = z End If

oldX = -5# fOldX = NormalX(oldX) newX = oldX + deltaX

Do While Not finished fNewX = NormalX(newX) sum = sum + (fOldX + fNewX)

fOldX = fNewX newX = newX + deltaX n=n+1 If (newX > tempZ) Then finished = True End If Loop

results(0) = sum * deltaX * 0.5

If z > 0 Then results(0) = 1 - results(0) End If

results(1) = n PrZ = results

End Function

Public Function NormalProb(X As Double, deltaX As Double) As Double Dim z As Double, results() As Double z = (X - fMu) / fSigma results = PrZ(z, deltaX) NormalProb = results(0) End Function

Public Function Inverse(prob As Double, mu As Double, variance As Double, deltaX As Double) As Double Dim result As Double, sum As Double, finished As Boolean

Dim X As Double, n As Integer, fOldX As Double, fNewX As Double Dim newX As Double

X = -5 fOldX = NormalX(X) newX = X + deltaX

Do While Not finished fNewX = NormalX(newX) sum = sum + 0.5 * deltaX * (fOldX + fNewX) fOldX = fNewX newX = newX + deltaX

If Abs(sum - prob) < 0.0001 Then finished = True End If Loop

Inverse = newX

End Function

Public Function BoxMuller() As Double() Dim z1 As Double, z2 As Double, u1 As Double, u2 As Double Dim randVariate() As Double ReDim randVariate(1) Const Pi = 3.1416

u1 = Rnd u2 = Rnd

z1 = ((-2 * Log(u1)) ^ 0.5) * Cos(2 * Pi * u2) z2 = ((-2 * Log(u1)) ^ 0.5) * Sin(2 * Pi * u2) randVariate(0) = fMean + (fVariance ^ 0.5) * z1 randVariate(1) = fMean + (fVariance ^ 0.5) * z2

BoxMuller = randVariate

End Function

Public Function inverseNormal() As Double Dim z As Double u = Rnd z = Application.WorksheetFunction.NormInv(u, fMean, fVariance) inverseNormal = fMean + (fVariance ^ 0.5) * z End Function

Public Function SimulateReturn() As Double Dim z As Double, R As Double R = Rnd z = Application.WorksheetFunction.NormInv(R, fMean, fVariance) SimulateReturn = fMean + (fVariance ^ 0.5) * z End Function

Public Function SimulateStockPrice(p0 As Double) As Double Dim p As Double, R As Double

R = SimulateReturn() p = p0 * Exp(R) SimulateStockPrice = p End Function

Public Function ProbLogNormal(a As Double, b As Double, n As Integer) As Double() Dim p As Double, R As Double, a1 As Double, b1 As Double Dim Pa As Double, Pb As Double Dim mean As Double, variance As Double, results() As Double ReDim results(1)

'parameter must only appear at the right handside of an assignment a1 = (Log(a) - n * fMu) / ((n ^ 0.5) * fSigma) b1 = (Log(b) - n * fMu) / ((n ^ 0.5) * fSigma) Pa = Application.WorksheetFunction.NormSDist(a1) Pb = Application.WorksheetFunction.NormSDist(b1) results(0) = Pb - Pa

mean = n * fMu ' = Exp(n * fMu + 0.5 * n * fvariance) variance = n * fVariance ' = Exp(n * 2 * fMu + n * fvariance) * (Exp(n * fvariance) - 1)

variance = variance ^ 0.5 results(1) = Application.WorksheetFunction.LogNormDist(b, mean, variance) Application.WorksheetFunction.LogNormDist(a, mean, variance) ProbLogNormal = results End Function

Public Function LogNormal(b As Double, n As Integer) As Double Dim p As Double, R As Double, b1 As Double, mean As Double, variance As Double b1 = (Log(b) - n * fMu) / ((n ^ 0.5) * fSigma) LogNormal = Application.WorksheetFunction.NormSDist(b1) End Function

Anda mungkin juga menyukai