Black-Scholes
Option Pricing Model
The value of a
call option
(based on the original B-S model) has been described as a function of
five
parameters:
The following
assumptions have been used in developing valuation models for options:
1. The rate of return on the stock follows a lognormal distribution.
This means that the logarithm of 1 plus the rate of return follows the
normal, or bell-shaped, curve. (The assumption ensures continuous
trading - the stock rate of return distribution is continuous.) 2. The
risk-free rate and variance of the return on the stock are constant
throughout the option’s life. (The two variables are nonstochastic.) 3.
There are no taxes or transaction costs. 4. The stock pays no
dividends. (This assumption ensures no jumps in the stock price. It is
well known that the stock price falls by approximately the amount of
the dividend on the ex-dividend date.) 5. The calls are European, which
does not allow for early exercise.
The B-S option pricing model is formulated as followed:
where N(•) = the
cumulative normal distribution function of (•).
In(•) = the natural logarithm of (•).
Once we have the price for a call option, we can derive the price of
the put option which written against the same stock with the same
exercise price using the put-call parity developed by Stoll in 1969:
In this example,
we derived call and put option price based on the Black-Scholes model.
The function procedures are used. The first function, SNorm(z),
computes the probability from negative infinity to z under standard
normal curve. This function provides results similar to those provided
by NORMSDIST( ) on Excel. The second function and the third function
compute call and put prices, respectively. The call price is computed
on cell C13, and the put price on cell C14. The two formulas are listed
on B17 and B18 for reference purpose.
'****************************************************************************
'*
Cumulative Standard Normal
Distribution
*
'* (This function
provides similar result as NORMSDIST( ) on Excel) *
'****************************************************************************
Function SNorm(z)
c1 = 2.506628
c2 = 0.3193815
c3 =
-0.3565638
c4 = 1.7814779
c5 = -1.821256
c6 = 1.3302744
If z > 0
Or z = 0 Then
w = 1
Else: w = -1
End If
y = 1 / (1 +
0.2316419 * w * z)
SNorm = 0.5 +
w * (0.5 - (Exp(-z * z / 2) / c1) * _
(y * (c2 + y * (c3 + y * (c4 + y * (c5 + y * c6))))))
End Function
'**********************************************************************
'*
Black-Scholes European Call Price Computation
*
'**********************************************************************
Function Call_Eur(s, x, t, r, sd)
Dim a As
Single
Dim b As
Single
Dim c As
Single
Dim d1 As
Single
Dim d2 As
Single
a = Log(s / x)
b = (r + 0.5
* sd ^ 2) * t
c = sd * (t ^
0.5)
d1 = (a + b)
/ c
d2 = d1 - sd
* (t ^ 0.5)
Call_Eur = s
* SNorm(d1) - x * Exp(-r * t) * SNorm(d2)
End Function
'*********************************************************************
'*
Black-Scholes European Put Price
Computation *
'*********************************************************************
Function Put_Eur(s, x, t, r, sd)
Dim a As
Single
Dim b As
Single
Dim c As
Single
Dim d1 As
Single
Dim d2 As
Single
a = Log(s / x)
b = (r + 0.5
* sd ^ 2) * t
c = sd * (t ^
0.5)
d1 = (a + b)
/ c
d2 = d1 - sd
* (t ^ 0.5)
CallEur = s *
SNorm(d1) - x * Exp(-r * t) * SNorm(d2)
Put_Eur = x *
Exp(-r * t) - s + CallEur
End Function
VBA
Codes