Binary Options are frequently classified as Exotic. The Binary Option business grew dramatically from 2008/9. Some elements of trading were regulated and others less so. Much of the unregulated industry was linked to Spotoption based in Israel - a privately held platform software provider. In January 2018, the binary options were banned in Israel following investigations by the FBI. European, Chinese and US authorities had banned unlicensed retail brokers prior to this. In the United States a number of regulated exchanges are permitted to trade binary options and in most wholesale financial markets large banks are also permitted to trade binary options.
Below, we explore the Binary Option Payoff. We compare this to Vanilla Call Option Payoff. It is clear that Binary or Digital Options produce much more dramatic outcomes. This attracts investors with stronger gambling predilections. The continuum between gambling and investment becomes less sharp in this space and regulators in recent years have become concerned with issues relating to unlicensed/unregistered brokers. To get some sense about how easy it was to set up a brokerage you might follow this link. In Europe, China and the United States, many types of binary options have been partially banned, with blanket bans being applied often to retail clients - such is the concern with scams in the sector. Below the payoffs are set up and explored in Microsoft Excel.
A binary option produces a binary payoff depending solely on the outcome of a yes/no or 1/0 contingency. Typically, this contingency relates to the behaviour of a specified asset. The binary option bet is comparable to a coin toss. Instead of flipping a coin however the payoff basically depends on whether a designated asset will increase above or decrease below some price level. In option parlance, we would more generally refer to an exercise price. The simplicity of the bet makes this type of product attractive (even addictive) to a growing segment of the retail market. A number of jurisdictions have gone so far as to imposing a ban on platforms that trade OTC binaries for non-professionals. The Times of Israel account of Digital Options trading provides an illuminating case study into how this OTC market combined with powerful fintech for harpooning clients can lead to chronic sub-optimal outcomes for investors.
For European style, binary options exercise automatically at expiry. Often the maturity of the bet is no longer than a few minutes or even seconds. These short timelines resemble the timelines characteristic of a casino or online betting platform where adrenaline is a key trigger. Binary options straddle both worlds because at their base they constitute a simple outcome of win or lose. Again not unlike the proposition embedded in racetrack or casino type bets. When modeling binaries, the parameter values we previously applied to the Black Scholes equally can be applied to Binaries when "fair game" premia have to be calculated. Unlike other types of options, a binary option characteristically does not give the holder the right to buy or sell the specified asset. When the binary option expires, the option holder receives either an arbitrary amount of cash or nothing at all. These binary options are often referred to as being Cash-or-Nothing. See below VBA code for Cash-or-Nothing for Reiner and Rubinstein (1991). We also provide some rough and ready numerical Greeks.
Function CashOrNothingCall(S, k, T, r, q, Sigma, Cash)
Dim d As Double
d = (Log(S / k) + (r - q - Sigma ^ 2 / 2) * T) / (Sigma * Sqr(T))
CashOrNothingCall = Cash * Exp(-r * T) * Application.NormSDist(d)
End Function
Function CashOrNothingPut(S, k, T, r, q, Sigma, Cash)
Dim d As Double
d = (Log(S / k) + (r - q - Sigma ^ 2 / 2) * T) / (Sigma * Sqr(T))
CashOrNothingPut = Cash * Exp(-r * T) * Application.NormSDist(-d)
End Function
'Greeks using Finite Difference
'Call
Function DeltaCNCash(S, k, T, r, q, Sigma, Cash)
dS = 0.001
DeltaCNCash = (CashOrNothingCall((S + dS), k, T, r, q, Sigma, Cash) - CashOrNothingCall((S - dS), k, T, r, q, Sigma, Cash)) / (2 * dS)
End Function
Function GammaCNCash(S, k, T, r, q, Sigma, Cash)
dS = 0.001
GammaCNCash = (DeltaCNCash(S + dS, k, T, r, q, Sigma, Cash) - DeltaCNCash(S - dS, k, T, r, q, Sigma, Cash)) / (2 * dS)
End Function
Function VegaCNCash(S, k, T, r, q, Sigma, Cash)
dSigma = 0.0000001
VegaCNCash = (CashOrNothingCall(S, k, T, r, q, (Sigma + dSigma), Cash) - CashOrNothingCall(S, k, T, r, q, (Sigma - dSigma), Cash)) / (2 * dSigma)
End Function
Function ThetaCNCash(S, k, T, r, q, Sigma, Cash)
dT = 0.0000001
ThetaCNCash = (CashOrNothingCall(S, k, (T + dT), r, q, Sigma, Cash) - CashOrNothingCall(S, k, (T - dT), r, q, Sigma, Cash)) / (-2 * dT)
End Function
Function RhoCNCash(S, k, T, r, q, Sigma, Cash)
dR = 0.0000001
RhoCNCash = (CashOrNothingCall(S, k, T, (r + dR), q, Sigma, Cash) - CashOrNothingCall(S, k, T, (r - dR), q, Sigma, Cash)) / (2 * dR)
End Function
'Put
Function DeltaPNCash(S, k, T, r, q, Sigma, Cash)
dS = 0.001
DeltaPNCash = (CashOrNothingPut((S + dS), k, T, r, q, Sigma, Cash) - CashOrNothingPut((S - dS), k, T, r, q, Sigma, Cash)) / (2 * dS)
End Function
Function GammaPNCash(S, k, T, r, q, Sigma, Cash)
dS = 0.001
GammaPNCash = (DeltaPNCash(S + dS, k, T, r, q, Sigma, Cash) - DeltaPNCash(S - dS, k, T, r, q, Sigma, Cash)) / (2 * dS)
End Function
Function VegaPNCash(S, k, T, r, q, Sigma, Cash)
dSigma = 0.0000001
VegaPNCash = (CashOrNothingPut(S, k, T, r, q, (Sigma + dSigma), Cash) - CashOrNothingPut(S, k, T, r, q, (Sigma - dSigma), Cash)) / (2 * dSigma)
End Function
Function ThetaPNCash(S, k, T, r, q, Sigma, Cash)
dT = 0.0000001
ThetaPNCash = (CashOrNothingPut(S, k, (T + dT), r, q, Sigma, Cash) - CashOrNothingPut(S, k, (T - dT), r, q, Sigma, Cash)) / (-2 * dT)
End Function
Function RhoPNCash(S, k, T, r, q, Sigma, Cash)
dR = 0.0000001
RhoPNCash = (CashOrNothingPut(S, k, T, (r + dR), q, Sigma, Cash) - CashOrNothingPut(S, k, T, (r - dR), q, Sigma, Cash)) / (2 * dR)
End Function
The Bull Spread is a trading strategy which is designed to profit from an expected rise in the price of the underlying asset. It can be created by using both puts and calls at different strike prices. Simultaneously, a call option at a lower strike price is bought and a call option at a higher price but with the same expiry date is sold. Please see video below explaining payoffs in Excel:
The Bull Spread as explained above can be manipulated to mimic the behaviour and payoff from Cash-or-Nothing Call Option. To see this we take the example demonstrated above and adjusted a few of the parameters so the Cash-or-Nothing Call payoff chart is consistent with payoff from holding a Bull Spread. This poses a problem for regulators. If regulators ban the sale and distribution of Binary Options, traders can synthetically created the same. Bull Spreads can not easily be banned because they are composed of vanilla style European Option positions. This creates opportunities for regulatory arbitrage. See Partnoy (2019) and previously Partnoy (1996) for a discussion of costs link to regulatory arbitrage.
Below we set out a number of lattice techniques for estimating Cash-or-Nothing binary options. We examine the level of accuracy consistent with Cox, Ross and Rubinstein (1979) (CRR)and Leisen Reimer (1996) (LR) relative to the European closed form solution presented by Reiner and Rubinstein (1991). We modified slightly some VBA code developed by Kerry Back and Espen Haug for originally estimating vanilla lattices.
' Modified from from Kerry Back for Binary Cash of Nothing Call
Function European_Call_Binomial_Cash(S, K, r, sigma, q, T, n, cash)
'
' Inputs are S = initial stock price
' K = strike price
' r = risk-free rate
' sigma = volatility
' q = dividend yield
' T = time to maturity
' N = number of time periods
'
Dim dt, u, d, pu, pd, u2, prob, CallV, i, Calle
dt = T / n ' length of time period
u = Exp(sigma * Sqr(dt)) ' size of up step
d = 1 / u ' size of down step
pu = (Exp((r - q) * dt) - d) / (u - d) ' probability of up step
pd = 1 - pu ' probability of down step
u2 = u * u
S = S * d ^ n ' stock price at bottom node at last date
prob = pd ^ n ' probability of bottom node at last date
If S > K Then
CallV = prob * cash ' probability weighted call value
Else
CallV = 0
End If
For i = 1 To n ' step up over nodes at last date
S = S * u2 ' stock price
prob = prob * (pu / pd) * (n - i + 1) / i ' probability
If S > K Then
Calle = cash ' probability weighted call value
Else
Calle = 0
End If
CallV = CallV + prob * Calle ' sum weighted values
Next i
European_Call_Binomial_Cash = Exp(-r * T) * CallV
End Function
' Modified from Espen Haug for Binary Cash-or-Nothing Option
'// Cox-Ross-Rubinstein binomial tree adapted for Binary
Public Function CRRBinomialB(cash As Double, CallPutFlag As String, S As Double, X As Double, T As Double, _
r As Double, b As Double, v As Double, n As Integer) As Variant
Dim OptionValue() As Double
Dim u As Double, d As Double, p As Double
Dim ReturnValue(4) As Double
Dim dt As Double, Df As Double
Dim i As Integer, j As Integer, z As Integer
ReDim OptionValue(0 To n + 1)
If CallPutFlag = "c" Then
z = 1
ElseIf CallPutFlag = "p" Then
z = -1
End If
dt = T / n
u = Exp(v * Sqr(dt))
d = 1 / u
p = (Exp(b * dt) - d) / (u - d)
Df = Exp(-r * dt)
For i = 0 To n
If z * S * u ^ i * d ^ (n - i) > z * X Then
OptionValue(i) = cash
Else
OptionValue(i) = 0
End If
Next
For j = n - 1 To 0 Step -1
For i = 0 To j
OptionValue(i) = (p * OptionValue(i + 1) + (1 - p) * OptionValue(i)) * Df
Next
If j = 2 Then
ReturnValue(2) = ((OptionValue(2) - OptionValue(1)) / (S * u ^ 2 - S) _
- (OptionValue(1) - OptionValue(0)) / (S - S * d ^ 2)) / (0.5 * (S * u ^ 2 - S * d ^ 2))
ReturnValue(3) = OptionValue(1)
End If
If j = 1 Then
ReturnValue(1) = (OptionValue(1) - OptionValue(0)) / (S * u - S * d)
End If
Next
ReturnValue(3) = (ReturnValue(3) - OptionValue(0)) / (2 * dt) / 365
ReturnValue(0) = OptionValue(0)
'Option
CRRBinomialB = ReturnValue(0)
'Delta
CRRBinomialB = ReturnValue(1)
'Gamma
CRRBinomialB = ReturnValue(2)
'Theta
CRRBinomialB = ReturnValue(3)
'Transpose
CRRBinomialB = Application.Transpose(ReturnValue())
End Function
The Leisen Reimer (1996) model (also) proves to be more accurate for pricing Binary Options. Again, we can determine accuracy relative to Reiner and Rubinstein (1991). We adapt some VBA code developed by Espen Haug when estimating the Leisen Reimer (1996) lattice for plain Vanilla European options. Below, we nest in conditions appropriate for Binary Call and Put Options
' Modified from Espen Haug for Binary Cash-or-Nothing Option
'// Leisen-Reimer binomial tree adapted for Binary
Public Function LeisenReimerBinomialB(cash As Double, CallPutFlag As String, S As Double, X As Double, T As Double, r As Double, b As Double, v As Double, n As Integer) As Variant
Dim OptionValue() As Double
Dim ReturnValue(3) As Double
Dim d1 As Double, d2 As Double
Dim hd1 As Double, hd2 As Double
Dim u As Double, d As Double, p As Double
Dim dt As Double, Df As Double
Dim i As Integer, j As Integer, z As Integer
n = Application.Odd(n)
ReDim OptionValue(0 To n)
If CallPutFlag = "c" Then
z = 1
ElseIf CallPutFlag = "p" Then
z = -1
End If
d1 = (Log(S / X) + (b + v ^ 2 / 2) * T) / (v * Sqr(T))
d2 = d1 - v * Sqr(T)
'// Using Preizer-Pratt inversion method 2
hd1 = 0.5 + Sgn(d1) * (0.25 - 0.25 * Exp(-(d1 / (n + 1 / 3 + 0.1 / (n + 1))) ^ 2 * (n + 1 / 6))) ^ 0.5
hd2 = 0.5 + Sgn(d2) * (0.25 - 0.25 * Exp(-(d2 / (n + 1 / 3 + 0.1 / (n + 1))) ^ 2 * (n + 1 / 6))) ^ 0.5
dt = T / n
p = hd2
u = Exp(b * dt) * hd1 / hd2
d = (Exp(b * dt) - p * u) / (1 - p)
Df = Exp(-r * dt)
For i = 0 To n
If z * S * u ^ i * d ^ (n - i) > z * X Then
OptionValue(i) = cash
Else
OptionValue(i) = 0
End If
Next
For j = n - 1 To 0 Step -1
For i = 0 To j
OptionValue(i) = (p * OptionValue(i + 1) + (1 - p) * OptionValue(i)) * Df
Next
If j = 2 Then
ReturnValue(2) = ((OptionValue(2) - OptionValue(1)) / (S * u ^ 2 - S * u * d) _
- (OptionValue(1) - OptionValue(0)) / (S * u * d - S * d ^ 2)) / (0.5 * (S * u ^ 2 - S * d ^ 2))
ReturnValue(3) = OptionValue(1)
End If
If j = 1 Then
ReturnValue(1) = (OptionValue(1) - OptionValue(0)) / (S * u - S * d)
End If
Next
ReturnValue(0) = OptionValue(0)
'Option value
LeisenReimerBinomialB = ReturnValue(0)
'Delta
LeisenReimerBinomialB = ReturnValue(1)
'Gamma
LeisenReimerBinomialB = ReturnValue(2)
'Transpose
LeisenReimerBinomialB = Application.Transpose(ReturnValue())
End Function