[Uwgarp-commits] r205 - in pkg/GARPFRM: R vignettes

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sun Jul 6 18:13:46 CEST 2014


Author: rossbennett34
Date: 2014-07-06 18:13:45 +0200 (Sun, 06 Jul 2014)
New Revision: 205

Added:
   pkg/GARPFRM/vignettes/BSM_and_Greeks.Rnw
   pkg/GARPFRM/vignettes/BinomialTrees.Rnw
Modified:
   pkg/GARPFRM/R/options.R
Log:
Adding vignettes for options

Modified: pkg/GARPFRM/R/options.R
===================================================================
--- pkg/GARPFRM/R/options.R	2014-07-03 15:59:55 UTC (rev 204)
+++ pkg/GARPFRM/R/options.R	2014-07-06 16:13:45 UTC (rev 205)
@@ -67,7 +67,7 @@
 #' euro.call <- optionSpec(style="european", type="call", S0=30, K=30, maturity=1, r=0.05, volatility=0.25, q=0)
 #' euro.call.val.bs <- optionValue(euro.call, method="Black-Scholes")
 #' @export
-optionValue <- function(option, method=c("Binomial", "Black-Scholes"), N=20, ...){
+optionValue <- function(option, method=c("Binomial", "Black-Scholes"), N=20, verbose=FALSE, ...){
   if(!is.option(option)) stop("option must be of class 'option'")
   
   style <- option$style
@@ -75,7 +75,7 @@
   
   if(style == "american"){
     if(method == "binomial" || method == "lattice"){
-      out <- americanBinomial(option, N)
+      out <- americanBinomial(option, N, verbose)
     } else {
       print(paste(method, " is not supported for an american option"))
       out <- NULL
@@ -85,7 +85,7 @@
   if(style == "european"){
     bs_methods <- c("black-scholes", "black-scholes-merton", "bs", "bsm")
     if(method == "binomial" || method == "lattice"){
-      out <- europeanBinomial(option, N)
+      out <- europeanBinomial(option, N, verbose)
     } else if(method %in% bs_methods){
       out <- europeanBS(option)
     } else {
@@ -99,7 +99,7 @@
 ##### Binomial Tree #####
 
 # Binomial tree to price a european option
-europeanBinomial <- function(option, N){
+europeanBinomial2 <- function(option, N){
   if(!is.option(option)) stop("option must be of class 'option'")
   if(option$style != "european") stop("must be a european option")
   
@@ -148,8 +148,106 @@
   return(A)
 }
 
+# Binomial tree to price a european option
+europeanBinomial <- function(option, N, verbose=FALSE){
+  if(!is.option(option)) stop("option must be of class 'option'")
+  if(option$style != "european") stop("must be a european option")
+  
+  # N: number of time steps
+  # type: call or put
+  # S0: initial asset value
+  # K: strike price
+  # r: continuously compounded yearly risk-free rate
+  # vol: annualized standard deviation of log return
+  # q: continuous dividend yield
+  # ttm: time to maturity (in years), i.e. the life of the option
+  
+  # Extract the parameters of the option
+  type <- option$type
+  S0 <- option$S0
+  K <- option$K
+  r <- option$r
+  vol <- option$volatility
+  q <- option$q
+  ttm <- option$maturity
+  
+  # 1 for call, -1 for put
+  if(type == "call"){
+    mult <- 1
+  } else if(type == "put") {
+    mult <- -1
+  } else {
+    mult <- 0
+  }
+  
+  # List to store option values
+  # These are used at the end to compute greeks
+  # option_value <- vector("list", 4)
+  
+  # Time step (delta t)
+  dt <- ttm / N
+  
+  # Size of up move
+  u <- exp(vol * sqrt(dt))
+  
+  # Size of down move
+  d <- exp(-vol * sqrt(dt))
+  
+  # Risk neutral probability of an uptick
+  p <- (exp((r - q) * dt) - d)/(u - d)
+  
+  # Discount factor
+  df <- exp(-r * dt)
+  
+  # At the terminal node, there are N+1 asset values
+  V <- pmax(0, mult * (S0 * (u^(0:N)) * (d^(N - (0:N))) - K))
+  # if(N == 4) option_value[[4]] <- V
+  
+  if(verbose){
+    cat("Time step: ", N, "\n", sep="")
+    cat("Prices:\n")
+    print(S0 * (u^(0:N)) * (d^(N - (0:N))))
+    cat("Option Values:\n")
+    print(V)
+  }
+  
+  # Iterate backward, such that there are j+1 asset values, where j is the
+  # Number of time steps
+  j.index <-seq(from=N-1, to=0, by=-1)
+  for (j in j.index) {
+    # S is the vector of prices at each time step and node
+    S <- S0 * (u^(0:j)) * (d^(j - (0:j)))
+    
+    # V.new is the vector of option values at each time step and node
+    V.new <- pmax(df * (p * V[2:(j+2)] + (1 - p) * V[1:(j+1)]), 0)
+    #if((j <= 4) & (j != 0)){
+    #  option_value[[j]] <- V.new
+    #}
+    V[1:(j+1)] <- V.new[1:(j+1)]
+    if(verbose){
+      cat("Time step: ", j, "\n", sep="")
+      cat("Prices:\n")
+      print(S)
+      cat("Option Values:\n")
+      print(V.new[1:(j+1)])
+    }
+  }
+  # calculate the greeks
+  #delta <- (f_02 - f_00) / (u^2 * S0 - d^2 * S0)
+  #delta <- (option_value[[2]][3] - option_value[[2]][1]) / (u^2 * S0 - d^2 * S0)
+  #delta_u <- (option_value[[2]][3] - option_value[[2]][2]) / (u^2 * S0 - S0)
+  #delta_d <- (option_value[[2]][2] - option_value[[2]][1]) / (S0 - d^2 * S0)
+  #gamma <- (delta_u - delta_d) / (0.5 * (u^2 * S0 - d^2 * S0))
+  #theta <- (f_22 - f_01) / (2 * dt)
+  #theta <- (option_value[[4]][3] - option_value[[2]][2]) / (2 * dt)
+  # The final value is the option price
+  f <- V[1]
+  #list(option_price=f, delta=delta, gamma=gamma, theta=theta, tree_values=option_value)
+  return(f)
+}
+
 # Binomial tree to price an american option
-americanBinomial <- function(option, N){
+americanBinomial <- function(option, N, verbose=FALSE){
   if(!is.option(option)) stop("option must be of class 'option'")
   if(option$style != "american") stop("must be an american option")
   
@@ -203,6 +301,14 @@
   V <- pmax(0, mult * (S0 * (u^(0:N)) * (d^(N - (0:N))) - K))
   # if(N == 4) option_value[[4]] <- V
   
+  if(verbose){
+    cat("Time step: ", N, "\n", sep="")
+    cat("Prices:\n")
+    print(S0 * (u^(0:N)) * (d^(N - (0:N))))
+    cat("Option Values:\n")
+    print(V)
+  }
+  
   # Iterate backward, such that there are j+1 asset values, where j is the
   # Number of time steps
   j.index <-seq(from=N-1, to=0, by=-1)
@@ -216,15 +322,21 @@
     #  option_value[[j]] <- V.new
     #}
     V[1:(j+1)] <- V.new[1:(j+1)]
-    #print(V)
+    if(verbose){
+      cat("Time step: ", j, "\n", sep="")
+      cat("Prices:\n")
+      print(S)
+      cat("Option Values:\n")
+      print(V.new[1:(j+1)])
+    }
   }
   # calculate the greeks
-  # delta <- (f_02 - f_00) / (u^2 * S0 - d^2 * S0)
+  #delta <- (f_02 - f_00) / (u^2 * S0 - d^2 * S0)
   #delta <- (option_value[[2]][3] - option_value[[2]][1]) / (u^2 * S0 - d^2 * S0)
   #delta_u <- (option_value[[2]][3] - option_value[[2]][2]) / (u^2 * S0 - S0)
   #delta_d <- (option_value[[2]][2] - option_value[[2]][1]) / (S0 - d^2 * S0)
   #gamma <- (delta_u - delta_d) / (0.5 * (u^2 * S0 - d^2 * S0))
-  # theta <- (f_22 - f_01) / (2 * dt)
+  #theta <- (f_22 - f_01) / (2 * dt)
   #theta <- (option_value[[4]][3] - option_value[[2]][2]) / (2 * dt)
   # The final value is the option price
   f <- V[1]
@@ -354,9 +466,11 @@
       plot(x = prices, y = out[[1]], type="l", ylab=greek, xlab="price", ...=...)
       plot(x = maturities, y = out[[2]], type="l", ylab=greek, xlab="time to maturity", ...=...)
       par(mfrow=c(1,1))
+      invisible(out)
+    } else {
+      # return the list
+      return(out)
     }
-    # return the list
-    return(out)
   }
   
   if(!is.null(prices)){
@@ -387,8 +501,10 @@
       xlab <- "price"
     }
     plot(x = xs, y = out, type="l", ylab=greek, xlab=xlab, ...=...)
+    invisible(out)
+  } else {
+    return(out)
   }
-  return(out)
 }
 
 #' @export
@@ -570,13 +686,13 @@
   # market price
   out <- vol_mid
   
-  out_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = out, ttm = ttm, P_mkt = P_mkt, type = type)^2
+  #out_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = out, ttm = ttm, P_mkt = P_mkt, type = type)^2
   # check the boundary conditions
-  lb_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = vol_lower, ttm = ttm, P_mkt = P_mkt, type = type)^2
-  if(lb_obj <= out_obj) warning("Objective function at lower boundary")
+  #lb_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = vol_lower, ttm = ttm, P_mkt = P_mkt, type = type)^2
+  #if(lb_obj <= out_obj) warning("Objective function at lower boundary")
   
-  ub_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = vol_upper, ttm = ttm, P_mkt = P_mkt, type = type)^2
-  if(ub_obj <= out_obj) warning("Objective function at upper boundary")
+  #ub_obj <- obj_fun(S0 = S0, K = K, r = r, q = q, sigma = vol_upper, ttm = ttm, P_mkt = P_mkt, type = type)^2
+  #if(ub_obj <= out_obj) warning("Objective function at upper boundary")
   
   return(out)
 }

Added: pkg/GARPFRM/vignettes/BSM_and_Greeks.Rnw
===================================================================
--- pkg/GARPFRM/vignettes/BSM_and_Greeks.Rnw	                        (rev 0)
+++ pkg/GARPFRM/vignettes/BSM_and_Greeks.Rnw	2014-07-06 16:13:45 UTC (rev 205)
@@ -0,0 +1,425 @@
+\documentclass{article}
+
+\usepackage{amsmath}
+\usepackage{Rd}
+\usepackage{verbatim}
+
+\usepackage[round]{natbib}
+\bibliographystyle{abbrvnat}
+
+%\VignetteIndexEntry{Black-Scholes-Merton and the Greeks}
+%\VignetteDepends{GARPFRM}
+%\VignettePackage{GARPFRM}
+
+\begin{document}
+
+<<echo=FALSE>>=
+library(knitr)
+suppressPackageStartupMessages(library(GARPFRM))
+opts_chunk$set(tidy=FALSE, warning=FALSE, fig.width=5, fig.height=5)
+@
+
+
+\title{Black-Scholes-Merton and the Greeks}
+\author{Ross Bennett}
+
+\maketitle
+
+\begin{abstract}
+The purpose of this vignette is to demonstrate the Black-Scholes-Merton pricing formulas and the "Greeks" as outlined in Chapter 4 and Chapter 5 of Valuation and Risk Models.
+\end{abstract}
+
+\tableofcontents
+
+\section{Black-Scholes-Merton Pricing Formulas}
+This section focuses on the application of the Black-Scholes-Merton pricing formulas for European call and put options. For derivation and theoretical background, the reader is encouraged to to study Chapter 4 of Valuation and Risk Models.
+
+The Black-Scholes-Merton pricing formulas for European call and put options are
+\begin{description}
+  \item[Call]
+  \begin{equation*}
+  c = S_0 N(d_1) - K e^{-rT} N(d_2)
+  \end{equation*}
+  \item[Put]
+  \begin{equation*}
+  p = K e^{-rT} N(-d_2) - S_0 N(-d_1)
+  \end{equation*}
+\end{description}
+
+where
+\begin{eqnarray*}
+  d_1 = \frac{\ln (S_0 / K) + (r + \sigma^2 / 2) T}{\sigma \sqrt{T}}\\
+  d_2 = \frac{\ln (S_0 / K) + (r - \sigma^2 / 2) T}{\sigma \sqrt{T}} = d_1 - \sigma \sqrt{T}\\
+  S_0 \quad \text{is the underlying stock price at $t = 0$}\\
+  K \quad \text{is the strike price}\\
+  r \quad \text{is the risk free rate}\\
+  T \quad \text{is the time to maturity in years}\\
+  \sigma \quad \text{is the volatility of the stock}\\
+  N(.) \quad \text{is the cumulative distribution function for a standard normal distribution}
+\end{eqnarray*}
+
+\subsection{Properties}
+For a call option, as the underlying price, $S_0$, becomes very large, the option will almost surely be exercised. The price of the call then becomes
+
+\begin{equation*}
+S_0 - K e^{-r T}
+\end{equation*}
+
+<<tidy=FALSE>>=
+# Demonstrate the property of the Black-Scholes-Merton formula for a call 
+# option as the underlying price becomes very large
+S0 <- seq(100, 100000, 100)
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = S0,
+                      K = 100,
+                      maturity = 1, 
+                      r = 0.1, 
+                      volatility = 0.2)
+call.price <- optionValue(option = eu.call, method = "Black-Scholes")
+plot(S0, call.price, xlab="Underlying Price", ylab="Call Price",
+     main="Call price as S_0 becomes very large", type="l")
+@
+
+<<tidy=FALSE>>=
+# Demonstrate the property of the Black-Scholes-Merton formula for a call 
+# option as the volatility approaches 0
+sigma <- seq(0.2, 0, -0.01)
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = 100,
+                      K = 100,
+                      maturity = 1, 
+                      r = 0.1, 
+                      volatility = sigma)
+call <- optionValue(option = eu.call, method = "Black-Scholes")
+# S_0 - K * e^{-r T}
+100 - 100 * exp(-0.1 * 1)
+plot(sigma, call, ylab="Call Price", ylab="Volatility", 
+     main="Call price as volatility approaches 0", type = "l")
+@
+
+
+Example 4.6: The stock price 6 months for the expiration of an option is \$42, the exercise price of the option is \$40, the risk-free interest rate is 10\% per annum, and the volatility is 20\% per annum.
+<<tidy=FALSE>>=
+# The stock price 6 months for the expiration of an option is $42, 
+# the exercise price of the option is $40, the risk-free interest 
+# rate is 10% per annum, and the volatility is 20% per annum.
+
+# Price the European call option
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = 42, 
+                      K = 40,
+                      maturity = 0.5, 
+                      r = 0.1, 
+                      volatility = 0.2)
+call <- optionValue(option = eu.call, method = "Black-Scholes")
+call
+
+# Price the European put option
+eu.put <- eu.call
+eu.put$type <- "put"
+put <- optionValue(option = eu.put, method = "Black-Scholes")
+put
+@
+
+\section{Implied Volatilities}
+The volatility the stock price is not directly observable and must be implied by option prices in the market. Here we calculate the implied volatility of a European call option with a price of \$1.875 and $S_0 = 21$, $K = 20$, $r = 0.1$, and $T = 0.25$. 
+<<tidy=FALSE>>=
+# Compute the implied volatility of a European call option with a 
+# price of $1.875 and S_0 = 21, K = 20, r = 0.1, and T = 0.25
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = 21, 
+                      K = 20,
+                      maturity = 0.25, 
+                      r = 0.1)
+impliedVolatility(eu.call, 1.875)
+@
+
+\section{Dividends}
+Example 4.9: Consider a European call option on a stock when there are ex-dividend dates in two months and five months. The dividend on each ex-dividend date is expected to be \$0.50. The current share price is \$40, the exercise price is \$40, and the stock price volatility is 30\% per annum, the risk-free rate of interest is 9\% per annum, and the time to maturity is 6 months. 
+Here we compute the value of a European call option with known dividends. 
+<<tidy=FALSE>>=
+# Consider a European call option on a stock when there are 
+# ex-dividend dates in two months and five months. The dividend 
+# on each ex-dividend date is expected to be \$0.50. The current 
+# share price is \$40, the exercise price is \$40, and the stock 
+# price volatility is 30\% per annum, the risk-free rate of 
+# interest is 9\% per annum, and the time to maturity is 6 months.
+
+# Subtract the present value of the dividends from the underlying price
+S0 <- 40 - (0.5 * exp(-0.09 * 2 / 12) + 0.5 * exp(-0.09 * 5 / 12))
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = S0, 
+                      K = 40,
+                      maturity = 0.5, 
+                      r = 0.09,
+                      volatility = 0.3)
+optionValue(eu.call, "Black-Scholes")
+@
+
+
+\section{The Greek Letters}
+This section introduces what is referred to as the "Greeks" for European options using the Black-Scholes-Merton formulas. The Greeks measure risk in a position in an option or portfolio of options.
+
+Here we create option specifications for call and put options that will be used in the following sections.
+<<tidy=FALSE>>=
+# Specify European call and put options where the current stock price is
+# $49, the strike price is $50, the risk-free rate is 5%, the time to
+# maturity is 20 weeks, and the volatility is 20%.
+
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = 49, 
+                      K = 50,
+                      maturity = 20/52, 
+                      r = 0.05,
+                      volatility = 0.2)
+
+eu.put <- optionSpec(style = "european", 
+                      type = "put", 
+                      S0 = 49, 
+                      K = 50,
+                      maturity = 20/52, 
+                      r = 0.05,
+                     volatility = 0.2)
+@
+
+
+\subsection{Delta}
+The delta ($\Delta$) of an option is defined as the rate of change of the option price with respect to the price of te underlying asset.
+
+The delta of a European option is given as
+\begin{eqnarray*}
+\Delta (call) = N(d_1)\\
+\Delta (put) = N(d_1) - 1\\
+\end{eqnarray*}
+
+<<>>=
+# Compute the delta of the European call option
+computeGreeks(eu.call, "delta")
+@
+
+
+<<tidy=FALSE>>=
+# Delta as the underlying price varies
+computeGreeks(eu.call, "delta", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Delta of call")
+computeGreeks(eu.put, "delta", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Delta of put")
+@
+
+<<tidy=FALSE>>=
+# Delta as the time to maturity varies for in the money, at the money, and
+# out of the money call options
+maturity <- seq(0.01, 1, 0.05)
+plot(maturity, xlim = range(maturity), ylim = c(0,1), 
+     type="n", xlab="Time to expiration", ylab="Delta")
+lines(x = maturity, y = deltaBS(52, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=2, col="blue")
+lines(x = maturity, y = deltaBS(50, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=1, col="black")
+lines(x = maturity, y = deltaBS(48, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=3, col="red")
+title("Delta of call")
+legend("topright", legend=c("In the money", "At the money", "Out of the money"),
+       lty=c(2,1,3), col=c("blue", "black", "red"), bty="n", cex=0.8)
+@
+
+The delta of a portfolio of options is simply the sum of the delta's of the individual options.
+
+\begin{equation*}
+\Delta_P = \sum_{i=1}^n w_i \Delta_i
+\end{equation*}
+
+Suppose a financial instituion has the following three positions in options on a stock.
+\begin{enumerate}
+  \item A long position in 100,000 call options with the strike price of \$55 and an expiration date in 3 months. The delta of each option is 0.533.
+  \item A short position in 200,000 call options with stick price of \$56 and an expiration date in 2 months. The delta of each option is 0.468.
+  \item A short position in 50,000 options with strike price of \$56 and an expiration date in 2 months. The delta of each option is -0.508.
+\end{enumerate}
+
+The delta of the portfolio is
+<<>>=
+100000 * 0.533 - 200000 * 0.468 - 50000 * -0.508
+@
+
+This means that the portfolio can be made delta neutral by purchasing 14,900 shares of the underlying stock.
+
+
+\subsection{Theta}
+The theta ($\Theta$) of an option is defined as the rate of change of the value of the option with respect to the passage of time with all else remaining equal.
+
+The theta of a European option is given as
+\begin{eqnarray*}
+\Theta (call) = - \frac{S_0 N'(d_1) \sigma}{2 \sqrt{T}} - r K e^{-r T} N(d_2)\\
+\Theta (put) = \frac{S_0 N'(d_1) \sigma}{2 \sqrt{T}} + r K e^{-r T} N(-d_2)\\
+\end{eqnarray*}
+
+where $N'(.)$ is the probability density function for a standard normal distribution.
+
+<<>>=
+# Compute the theta of the European call option
+computeGreeks(eu.call, "theta")
+@
+
+<<tidy=FALSE>>=
+# Theta as the underlying price varies
+computeGreeks(eu.call, "theta", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Theta of call")
+@
+
+<<tidy=FALSE>>=
+# Theta as the time to maturity varies for in the money, at the money, and
+# out of the money call options
+maturity <- seq(0.01, 1, 0.05)
+plot(maturity, xlim = range(maturity), ylim = c(-15,0), 
+     type="n", xlab="Time to expiration", ylab="Theta")
+lines(x = maturity, y = thetaBS(55, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=2, col="blue")
+lines(x = maturity, y = thetaBS(50, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=1, col="black")
+lines(x = maturity, y = thetaBS(45, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=3, col="red")
+title("Theta of call")
+legend("topright", legend=c("In the money", "At the money", "Out of the money"),
+       lty=c(2,1,3), col=c("blue", "black", "red"), bty="n", cex=0.8)
+@
+
+\subsection{Gamma}
+The gamma ($\Gamma$) of an option is defined as the rate of change of the delta of the option with respect to the price of the underlying asset.
+
+The gamma of a European option is given as
+\begin{equation*}
+\Gamma = \frac{N'(d_1)}{S_0 \sigma \sqrt{T}}
+\end{equation*}
+
+Note that the gamma for a European put option is equal to the gamma of a European call option.
+
+<<>>=
+# Compute the gamma of the European call option
+computeGreeks(eu.call, "gamma")
+@
+
+<<tidy=FALSE>>=
+# Gamma as the underlying price varies
+computeGreeks(eu.call, "gamma", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Gamma of call")
+@
+
+<<tidy=FALSE>>=
+# Gamma as the time to maturity varies for in the money, at the money, and
+# out of the money call options
+maturity <- seq(0.01, 1, 0.05)
+plot(maturity, xlim = range(maturity), ylim = c(0,0.5), 
+     type="n", xlab="Time to expiration", ylab="Gamma")
+lines(x = maturity, y = gammaBS(55, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=2, col="blue")
+lines(x = maturity, y = gammaBS(50, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=1, col="black")
+lines(x = maturity, y = gammaBS(45, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=3, col="red")
+title("Gamma of call")
+legend("topright", legend=c("In the money", "At the money", "Out of the money"),
+       lty=c(2,1,3), col=c("blue", "black", "red"), bty="n", cex=0.8)
+@
+
+\subsection{Vega}
+The vega ($\nu$) of an option is defined as the rate of change of the value of the option with respect to the volatility of the underlying asset.
+
+The vega of a European option is given as
+\begin{equation*}
+\nu = S_0 \sqrt{T} N'(d_1)
+\end{equation*}
+
+Note that the vega for a European put option is equal to the vega of a European call option.
+
+<<>>=
+# Compute the vega of a European call option
+computeGreeks(eu.call, "vega")
+@
+
+<<tidy=FALSE>>=
+# Vega as the underlying price varies
+computeGreeks(eu.call, "vega", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Vega of call")
+@
+
+<<tidy=FALSE>>=
+# Vega as the time to maturity varies for in the money, at the money, and
+# out of the money call options
+maturity <- seq(0.01, 1, 0.05)
+plot(maturity, xlim = range(maturity), ylim = c(0,20), 
+     type="n", xlab="Time to expiration", ylab="Theta")
+lines(x = maturity, y = vegaBS(55, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=2, col="blue")
+lines(x = maturity, y = vegaBS(50, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=1, col="black")
+lines(x = maturity, y = vegaBS(45, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=3, col="red")
+title("Vega of call")
+legend("topleft", legend=c("In the money", "At the money", "Out of the money"),
+       lty=c(2,1,3), col=c("blue", "black", "red"), bty="n", cex=0.8)
+@
+
+\subsection{Rho}
+The rho ($\rho$) of an option is defined as the rate of change of the value of the option with respect to the risk-free interest rate.
+
+The rho of a European option is given as
+\begin{eqnarray*}
+\rho (call) = K T e^{-r T} N(d_2)\\
+\rho (put) = -K T e^{-r T} N(-d_2)\\
+\end{eqnarray*}
+
+
+<<>>=
+# Compute the rho of the European call option
+computeGreeks(eu.call, "rho")
+@
+
+<<tidy=FALSE>>=
+# Rho as the unerlying price varies
+computeGreeks(eu.call, "rho", prices = seq(20, 80, 1), 
+              plot = TRUE, main="Rho of call")
+@
+
+<<tidy=FALSE>>=
+# Rho as the time to maturity varies for in the money, at the money, and
+# out of the money call options
+maturity <- seq(0.01, 1, 0.05)
+plot(maturity, xlim = range(maturity), ylim = c(0,40), 
+     type="n", xlab="Time to expiration", ylab="Theta")
+lines(x = maturity, y = rhoBS(55, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=2, col="blue")
+lines(x = maturity, y = rhoBS(50, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=1, col="black")
+lines(x = maturity, y = rhoBS(45, 50, 0.05, 0, 0.2, maturity, "call"), 
+      lty=3, col="red")
+title("Rho of call")
+legend("topleft", legend=c("In the money", "At the money", "Out of the money"),
+       lty=c(2,1,3), col=c("blue", "black", "red"), bty="n", cex=0.8)
+@
+
+\subsection{Portfolio Insurance}
+Example 5.9: A portfolio with worth \$90 million. To protect against market downturns the managers of the portfolio require a 6-month European put option on the portfolio with a strike price of \$87 million. The risk-free rate is 9\% per annum, the dividend yield is 3\% per annum, and the volatility of the portfolio is 20\% per annum. The S\&P 500 index stands at 900. As the portfolio is considered to mimic the S\&P 500 fairly closely, one alternative is to buy 1000 put options on the S\&P 500 with a strike price of 870. Another option is to create the option synthetically. In this case, $S_0 = 90$ million, $K = 87$ million, $r = 0.09$, $q = 0.03$, $\sigma = 0.25$, and $T = 0.5$.
+
+<<tidy=FALSE>>=
+eu.put <- optionSpec(style = "european", 
+                     type = "put", 
+                     S0 = 90, 
+                     K = 87,
+                     maturity = 0.5, 
+                     r = 0.09,
+                     volatility = 0.25,
+                     q = 0.03)
+computeGreeks(eu.put, "delta")
+@
+
+The delta of the synthetic option is -0.3215. This means that 32.15\% of the portfolio should be sold to match the delta of the synthetic option.
+
+\bibliography{GARPFRM}
+
+\end{document}

Added: pkg/GARPFRM/vignettes/BinomialTrees.Rnw
===================================================================
--- pkg/GARPFRM/vignettes/BinomialTrees.Rnw	                        (rev 0)
+++ pkg/GARPFRM/vignettes/BinomialTrees.Rnw	2014-07-06 16:13:45 UTC (rev 205)
@@ -0,0 +1,208 @@
+\documentclass{article}
+
+\usepackage{amsmath}
+\usepackage{Rd}
+\usepackage{verbatim}
+
+\usepackage[round]{natbib}
+\bibliographystyle{abbrvnat}
+
+%\VignetteIndexEntry{Binomial Trees}
+%\VignetteDepends{GARPFRM}
+%\VignettePackage{GARPFRM}
+
+\begin{document}
+
+<<echo=FALSE>>=
+library(knitr)
+suppressPackageStartupMessages(library(GARPFRM))
+opts_chunk$set(tidy=FALSE, warning=FALSE, fig.width=5, fig.height=5)
+@
+
+
+\title{Binomial Trees}
+\author{Ross Bennett}
+
+\maketitle
+
+\begin{abstract}
+The purpose of this vignette is to demonstrate valuing an option by constructing a binomial tree as outlined in Chapter 3 of Valuation and Risk Models.
+\end{abstract}
+
+\tableofcontents
+
+\section{One-Step Binomial Tree}
+\subsection{No-Arbitrage Argument}
+We start with a simple example to introduce the concept of a one-step binomial tree to value a European call option with a strike price of \$21 and time to maturity of 3 months. Suppose that the current price of a stock is \$20 and we know with certainty that the price will be either \$18 or \$22 in three months. In three months, there are two possible outcomes and the option has two possible values. If the price is \$22, the value of the option will be \$1. If the price is \$18, the value of the option will be \$0.
+
+INSERT IMAGE OF 1-STEP TREE
+
+To value the option, we form a riskless portfolio consisting of the stock and the option. In the absence of arbitrage opportunities, it is possible to form a portfolio such that there is no uncertainty about the value of the portfolio at the end of the 3 months. We form a portfolio such that we short the call option and buy $\Delta$ shares of the underlying stock. Here we calculate the value of the portfolio for the two possible outcomes at the end of the 3 months.
+
+\begin{description}
+  \item[The stock price is \$22]
+  The value of the portfolio is \$22 $\Delta$ - 1 
+  
+  \item[The stock price is \$18]
+  The value of the portfolio is \$18 $\Delta$
+\end{description}
+
+Now we solve for $\Delta$ to determine the number of shares of the underlying stock we need to purchase for our portfolio.
+
+\begin{eqnarray*}
+22 \Delta - 1 &=& 18 \Delta\\
+\Delta &=& 0.25
+\end{eqnarray*}
+
+Therefore, our riskless portfolio is long $\Delta = 0.25$ shares of stock and short 1 call option. At the end of 3 months, the value of our portfolio is $22 * 0.25 - 1 = 18 * 0.25 = 4.5$. This confirms that our portfolio value is the same if the stock price increases to \$22 or decreases to \$18. One way to interpret $\Delta$ is the number of shares of the underlying stock to purchase to hedge our short position in the call option. We make the argument that in the abscence of arbitrage, the riskless portfolio must earn the risk free rate. Let the current risk free rate be 12\% per annum. The current value of the portfolio is the present value of 4.5
+
+\begin{equation*}
+4.5 e^{-0.12 * 3 / 12} = 4.367
+\end{equation*}
+
+Here we calculate the value of our portfolio today. Let $f$ denote the price of the option.
+
+\begin{eqnarray*}
+20 \Delta - f &=& 4.367\\
+20 * 0.25 - f &=& 4.367\\
+\end{eqnarray*}
+
+Now we solve for $f$ to determine the value of the option.
+\begin{eqnarray*}
+f &=& 20 * 0.25 - 4.367\\
+f &=& 0.633
+\end{eqnarray*}
+
+
+The above approach generalizes to the following equations:
+\begin{eqnarray*}
+p &=& \frac{e^{rT} - d}{u - d}\\
+f &=& e^{-r T} (p * f_u + (1 - p) * f_d)\\
+\end{eqnarray*}
+
+where
+\begin{description}
+  \item[$p$] is the probability of an up movement in the stock price
+  \item[$r$] is the risk free rate per annum
+  \item[$T$] is the time to maturity in years
+  \item[$u$] is defined such that the $u-1$ is the percentage increase in the stock price when there is an up movement
+  \item[$d$] is defined such that $1-d$ is the percentage decrease in the stock price when there is a down movement
+  \item[$f$] is the value of the option
+  \item[$f_u$] is the option value if the stock price moves up
+  \item[$f_d$] is the the option value if the stock moves down
+\end{description}
+
+\subsection{Risk-Neutral Valuation}
+We can also value the option in a risk-neutral framework. Refer to the FRM text for a detailed description of risk-neutral valuation. Here we interpret $p$ as the probability of an up movement and $1 - p$ as the probability of a down movement in a risk neutral world. We can make the argument that, in a risk neutral world, the expected return of a stock must be equal to the risk free rate.
+
+The expected value of a stock at time $t$ is given by
+\begin{eqnarray*}
+E[S_t] = p * S_0 * u + (1 - p) * S_0 * d
+\end{eqnarray*}
+
+where $S_0$ is the price of the stock at time $t=0$.
+
+Substiuting $p = (e^{rT} - d) / (u - d)$ gives
+\begin{eqnarray*}
+E[S_t] = S_0 *e^{rT}
+\end{eqnarray*}
+
+Therefore $p$ must satisfy
+\begin{eqnarray*}
+22 * p + 18 * (1 - p) &=& 20 * e^{0.12 * 3 / 12}\\
+p &=& 0.6532
+\end{eqnarray*}
+
+This means that at the end of the 3 months the value of the call option is \$1 with probability 0.6532 or value of \$0 with probability 0.3468. The expected value of the option is
+\begin{equation*}
+1 * 0.6532 + 0 * (1 - 0.6532) = 0.6532
+\end{equation*}
+
+We discount at the risk free rate in a risk-neutral world, therefore the value of the option today is
+\begin{equation*}
+0.6532 * e^{0.12 * 3 / 12} = 0.633
+\end{equation*}
+
+We have shown that valuing the option in the risk neutral world gives the same answer as valuing the option with no arbitrage arguments.
+
+\section{Two-Step and N-Step Binomial Trees}
+The approach of the one-step binomial tree can applied to a two-step binomial tree and extended further to a binomial tree with $N$ steps. When using a binomial tree to value an option, the goal is to compute the option value at the initial node where time $t = 0$. For a binomial tree, we recursively move backwards through the tree, computing the stock price and option value at each node  until we reach the initial node.
+
+INSERT IMAGE OF TWO-STEP TREE
+
+INSERT IMAGE OF N-STEP TREE
+
+\section{American Options}
+When valuing American style options, we must consider early exercise. To account for early exercise, we recursively work backwards through the tree as in the previously example. The difference is that when computing the option value at each node, we must compare option payoff from early exercise to the expected value of the option. At each node, the value of the option is the greater of
+
+\begin{enumerate}
+  \item Option Expected Value
+  \begin{equation*}
+  e^{-r \Delta t} ( p * f_u + (1 - p) f_d)
+  \end{equation*}
+  \item
+  Option Payoff from Early Exercise\newline
+  max($S_t - K$, 0) for a call option or max($K - S_t$, 0) for a put option.
+\end{enumerate}
+
+<<tidy=FALSE>>=
+am.put <- optionSpec(style = "american", 
+                      type = "put", 
+                      S0 = 50, 
+                      K = 52, 
+                      maturity = 2, 
+                      r = 0.05, 
+                      volatility = 0.3)
+am.value <- optionValue(am.put, "Binomial", 2, verbose = TRUE)
+@
+
+\section{Formual Summary}
+Here we summarize formulas to construct the binomial tree
+
+Calibrate $u$ and $d$ to the volatility of the stock price:
+\begin{eqnarray*}
+u &=& e^{\sigma \sqrt{\Delta t}}\\
+d &=& e^{-\sigma \sqrt{\Delta t}}\\
+\end{eqnarray*}
+
+The probability of an up movement is given as
+\begin{eqnarray*}
+p = \frac{e^{r \Delta t} - d}{u - d}
+\end{eqnarray*}
+
+where
+\begin{description}
+  \item[$r$] is the risk free rate
+  \item[$\Delta t$] is the time step
+\end{description}
+
+
+\section{Examples}
+<<tidy=FALSE>>=
+eu.call <- optionSpec(style = "european", 
+                      type = "call", 
+                      S0 = 810, 
+                      K = 800, 
+                      maturity = 0.5, 
+                      r = 0.05, 
+                      volatility = 0.2,
+                      q = 0.02)
+eu.value <- optionValue(eu.call, "Binomial", 2, verbose = TRUE)
+@
+
+
+<<tidy=FALSE>>=
+am.call <- optionSpec(style = "american", 
+                      type = "call", 
+                      S0 = 0.61, 
+                      K = 0.6, 
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/uwgarp -r 205


More information about the Uwgarp-commits mailing list