[R] Secant Method Convergence (Method to replicate Excel XIRR/IRR)

Ravi Varadhan rvaradhan at jhmi.edu
Thu Aug 26 05:36:20 CEST 2010


I have written a general root-finder using the secant method.  

secant <- function(par, fn, tol=1.e-07, itmax = 100, trace=TRUE, ...) {
# par = a starting vector with 2 starting values
# fn = a function whose first argument is the variable of interest
# 
if (length(par) != 2) stop("You must specify a starting parameter vector of length 2") 
p.2 <- par[1]
p.1 <- par[2]
f <- rep(NA, length(par))
f[1] <- fn(p.1, ...)
f[2] <- fn(p.2, ...)
iter <- 1
pchg <- abs(p.2 - p.1)
fval <- f[2]
if (trace) cat("par: ", par, "fval: ", f, "\n")
while (pchg >= tol & abs(fval) > tol & iter <= itmax) {
	p.new <- p.2 - (p.2 - p.1) * f[2] / (f[2] - f[1])
	pchg <- abs(p.new - p.2)
	fval <- fn(p.new, ...)
	p.1 <- p.2
	p.2 <- p.new
	f[1] <- f[2]
	f[2] <- fval
	iter <- iter + 1
if (trace) cat("par: ", p.new, "fval: ", fval, "\n")
}
list(par = p.new, value = fval, iter=iter)
}

Now we can use this function to find the zero of your NPV function as follows:

npv <- function (irr, cashFlow, times) sum(cashFlow / (1 + irr)^times)

CF <- c(-1000,500,500,500,500,500)

dates <- c("1/1/2001","2/1/2002","3/1/2003","4/1/2004","5/1/2005","6/1/2006") 
cfDate <- as.Date(cfDate,format="%m/%d/%Y")
times <- as.numeric(difftime(cfDate, cfDate[1], units="days"))/365.24

secant(par=c(0,0.1), fn=npv, cashFlow=CF, times=times)

> secant(par=c(0,0.1), fn=npv, cashFlow=CF, times=times)
par:  0 0.1 fval:  854.2388 1500 
par:  0.232284 fval:  334.7318 
par:  0.2990093 fval:  156.9595 
par:  0.3579227 fval:  30.59229 
par:  0.3721850 fval:  3.483669 
par:  0.3740179 fval:  0.08815743 
par:  0.3740655 fval:  0.0002613245 
par:  0.3740656 fval:  1.966778e-08 
$par
[1] 0.3740656

$value
[1] 1.966778e-08

$iter
[1] 8


Hope this helps,
Ravi.

____________________________________________________________________

Ravi Varadhan, Ph.D.
Assistant Professor,
Division of Geriatric Medicine and Gerontology
School of Medicine
Johns Hopkins University

Ph. (410) 502-2619
email: rvaradhan at jhmi.edu


----- Original Message -----
From: Ravi Varadhan <rvaradhan at jhmi.edu>
Date: Wednesday, August 25, 2010 10:51 pm
Subject: Re: [R] Secant Method Convergence (Method to replicate Excel XIRR/IRR)
To: Adrian Ng <ang at hamiltonlane.com>
Cc: "r-help at r-project.org" <r-help at r-project.org>


> You should use cfDate[1] as the time origin.  You cannot use 
> 08-24-2010 as the time origin, since that will yield negative times.  
> 
>  
>  Here is the correct solution.  
>  
>  ANXIRR <- function (cashFlow, dates, guess, tol=1.e-04){
>  
>  npv <- function (cashFlow, times, irr) {
>  n <- length(cashFlow)
>  sum(cashFlow / (1 + irr)^times)
>  }
>  
>  if (guess == 0) stop("Initial guess must be strictly greater than 0") 
> 
>  
>  cfDate <- as.Date(cfDate,format="%m/%d/%Y")
>  times <- as.numeric(difftime(cfDate, cfDate[1], units="days") /
>  365.24)
>  
>  irrprev <- c(0)
>  irr <- guess
>  pvPrev <- sum(cashFlow)
>  pv <- npv(cashFlow, times, irr)
>  eps <- abs(pv-pvPrev)
>  
>  while (eps >= tol) {
>  tmp <- irrprev 
>  irrprev <- irr
>  irr <- irr - ((irr - tmp) * pv / (pv - pvPrev))
>  pvPrev <- pv
>  pv <- npv(cashFlow, times, irr)
>  eps <- abs(pv - pvPrev)
>  }
>  list(irr = irr, npv = pv)
>  }
>  CF <- c(-1000,500,500,500,500,500)
>  
>  dates <- 
> c("1/1/2001","2/1/2002","3/1/2003","4/1/2004","5/1/2005","6/1/2006") 
>  
>  ANXIRR(CF, dates, guess=0.1)
>  
>  > ANXIRR(CF, dates, guess=0.1)
>  $irr
>  [1] 0.3740656
>  
>  $npv
>  [1] 2.102695e-09
>  
>  
>  Hope this helps,
>  Ravi.
>  
>  ____________________________________________________________________
>  
>  Ravi Varadhan, Ph.D.
>  Assistant Professor,
>  Division of Geriatric Medicine and Gerontology
>  School of Medicine
>  Johns Hopkins University
>  
>  Ph. (410) 502-2619
>  email: rvaradhan at jhmi.edu
>  
>  
>  ----- Original Message -----
>  From: Adrian Ng <ang at hamiltonlane.com>
>  Date: Wednesday, August 25, 2010 8:33 pm
>  Subject: RE: [R] Secant Method Convergence (Method to replicate Excel 
> XIRR/IRR)
>  To: Ravi Varadhan <rvaradhan at jhmi.edu>
>  Cc: "r-help at r-project.org" <r-help at r-project.org>
>  
>  
>  > Hi Ravi,
>  >  
>  >  Using days and dividing it by 365 effectively converts the number 
> to 
>  > years anyway and allows for the irregular times to be specific to 
> the 
>  > days.
>  >  
>  >  Also, when I replace dates[1] in your line:
>  >   times <- as.numeric(difftime(dates, dates[1], units="days") /
>  >  365.24) with "2010-08-24" I think I am getting some irregular 
>  > results.  
>  >  
>  >  Effectively, what I was trying to do was match what Excel produced 
> 
>  > with its XIRR function.  With the example I gave excel returned an 
> IRR 
>  > of ~0.37 (or 37%)
>  >  
>  >  I am still in the process of debugging it...
>  >  
>  >  
>  >  
>  >   
>  >  
>  >  -----Original Message-----
>  >  From: Ravi Varadhan [ 
>  >  Sent: Wednesday, August 25, 2010 7:24 PM
>  >  To: Adrian Ng
>  >  Cc: r-help at r-project.org
>  >  Subject: RE: [R] Secant Method Convergence (Method to replicate 
> Excel 
>  > XIRR/IRR)
>  >  
>  >  The secant method converges just fine.  Your problem might have 
>  > occurred due
>  >  to improper conversion of dates to elapsed time.  You want to 
>  > calculate IRR
>  >  using "year" as the time unit, not "days".  
>  >  
>  >  Here is the secant function (modified to account for irregular 
> times) 
>  > and
>  >  the results for your example:
>  >  
>  >  ANXIRR <- function (cashFlow, dates, guess, tol=1.e-04){
>  >  
>  >  npv <- function (cashFlow, times, irr) {
>  >  	n <- length(cashFlow)
>  >  	sum(cashFlow / (1 + irr)^times)
>  >  	}
>  >  
>  >  if (guess == 0)stop("Initial guess must be strictly greater than 
> 0")  
>  > 
>  >  
>  >  	times <- as.numeric(difftime(dates, dates[1], units="days") /
>  >  365.24)
>  >  
>  >          irrprev <- c(0)
>  >            irr <- guess
>  >          pvPrev <- sum(cashFlow)
>  >          pv <- npv(cashFlow, times, irr)
>  >  	eps <- abs(pv-pvPrev)
>  >  
>  >  while (eps >= tol) {
>  >          tmp <- irrprev 
>  >           irrprev <- irr
>  >          irr <- irr - ((irr - tmp) * pv / (pv - pvPrev))
>  >          pvPrev <- pv
>  >          pv <- npv(cashFlow, times, irr)
>  >           eps <- abs(pv - pvPrev)
>  >          }
>  >  	list(irr = irr, npv = pv)
>  >  }
>  >  
>  >  CF <- c(-1000,500,500,500,500,500)
>  >  
>  >  dates <-
>  >  
> c("1/1/2001","2/1/2002","3/1/2003","4/1/2004","5/1/2005","6/1/2006") 
>  > 
>  >  
>  >  ANXIRR(CF, dates, guess=0.1)
>  >  
>  >  > ANXIRR(CF, dates, guess=0.1)
>  >  $irr
>  >  [1] 0.4106115
>  >  
>  >  $npv
>  >  [1] 2.984279e-13
>  >  
>  >  
>  >  Ravi.
>  >  
>  >  -----Original Message-----
>  >  From: Adrian Ng [ 
>  >  Sent: Wednesday, August 25, 2010 6:23 PM
>  >  To: Ravi Varadhan
>  >  Subject: RE: [R] Secant Method Convergence (Method to replicate Excel
>  >  XIRR/IRR)
>  >  
>  >  The forum is kind of slow so I'm just re-sending you the message here:
>  >  
>  >  Hi Ravi, 
>  >  
>  >  I'm just trying a fairly simple example: 
>  >  CFs: -1000,500,500,500,500,500 
>  >  
>  > 
> dates<-c("1/1/2001","2/1/2002","3/1/2003","4/1/2004","5/1/2005","6/1/2006") 
> 
>  > 
>  >  
>  >  Thanks a lot for your help. 
>  >  Adrian
>  >  
>  >  -----Original Message-----
>  >  From: Ravi Varadhan [ 
>  >  Sent: Wednesday, August 25, 2010 5:44 PM
>  >  To: Adrian Ng; r-help at r-project.org
>  >  Subject: RE: [R] Secant Method Convergence (Method to replicate Excel
>  >  XIRR/IRR)
>  >  
>  >  Yes, the secant method (like Newton Raphson) is not guaranteed to 
> converge,
>  >  unlike the bisection method, but it has a superlinear convergence 
> 
>  > (not that
>  >  this matters much!).  Brent's method, which is used in `uniroot', 
> is 
>  > a
>  >  reliable and fast method, which is why I suggested it in my 
> previous 
>  > email.
>  >  
>  >  Having said that, I am not sure about the convergence problem that 
> 
>  > you are
>  >  having without seeing the actual example.
>  >  
>  >  Ravi.
>  >  
>  >  -----Original Message-----
>  >  From: Adrian Ng [ 
>  >  Sent: Wednesday, August 25, 2010 5:28 PM
>  >  To: Ravi Varadhan; r-help at r-project.org
>  >  Subject: RE: [R] Secant Method Convergence (Method to replicate Excel
>  >  XIRR/IRR)
>  >  
>  >  Hi Ravi,
>  >  
>  >  Thanks for the responses.  I was actually trying to calculate IRR 
> 
>  > based on
>  >  unevenly spaced cash flows, and that's why I decided to use the secant
>  >  method.  I'm not sure if my answer isn't converging because I have 
> some
>  >  careless mistake in the code, or if it's simply because unlike the 
> bisection
>  >  method, the secant method doesn't 'sandwich' the desired root.
>  >  
>  >  
>  >  
>  >  -----Original Message-----
>  >  From: Ravi Varadhan [ 
>  >  Sent: Wednesday, August 25, 2010 5:24 PM
>  >  To: Adrian Ng; r-help at r-project.org
>  >  Subject: RE: [R] Secant Method Convergence (Method to replicate Excel
>  >  XIRR/IRR)
>  >  
>  >  Another approach is to use `uniroot' to find the zero of the NPV function:
>  >  
>  >  npv <- function (cashFlow, irr) {
>  >  	n <- length(cashFlow)
>  >  	sum(cashFlow / (1 + irr)^{0: (n-1)})
>  >  	}
>  >  
>  >  uniroot(f=npv, interval=c(0,1), cashFlow=cashFlow)
>  >  
>  >  However, there may be situations where there are no real zeros or 
> 
>  > there are
>  >  multiple zeros of the NPV function.
>  >  
>  >  Ravi.
>  >  
>  >  -----Original Message-----
>  >  From: r-help-bounces at r-project.org [ On
>  >  Behalf Of Adrian Ng
>  >  Sent: Wednesday, August 25, 2010 8:39 AM
>  >  To: r-help at r-project.org
>  >  Subject: [R] Secant Method Convergence (Method to replicate Excel 
> XIRR/IRR)
>  >  
>  >  Hi,
>  >  
>  >  I am new to R, and as a first exercise, I decided to try to 
> implement 
>  > an
>  >  XIRR function using the secant method.  I did a quick search and 
> saw 
>  > another
>  >  posting that used the Bisection method but wanted to see if it was 
> possible
>  >  using the secant method.
>  >  
>  >  I would input a Cash Flow and Date vector as well as an initial 
>  > guess.  I
>  >  hardcoded today's initial date so I could do checks in Excel.  
> This code
>  >  seems to only converge when my initial guess is very close to the 
> correct
>  >  IRR.
>  >  
>  >  Maybe I have some basic errors in my coding/logic? Any help would 
> be 
>  > greatly
>  >  appreciated.
>  >  
>  >  The Wikipedia article to secant method and IRR:
>  >  
>  >  
>  >  Thanks!
>  >  
>  >  
>  >  
>  >  ANXIRR <- function (cashFlow, cfDate, guess){
>  >          cfDate<-as.Date(cfDate,format="%m/%d/%Y")
>  >          irrprev <- c(0); irr<- guess
>  >  
>  >  
>  >          pvPrev<- sum(cashFlow)
>  >          pv<-
>  >  sum(cashFlow/((1+irr)^(as.numeric(difftime(cfDate,"2010-08-24",units="days")
>  >  )/360)))
>  >          print(pv)
>  >          print("Hi")
>  >  
>  >  
>  >  while (abs(pv) >= 0.001) {
>  >          t<-irrprev; irrprev<- irr;
>  >          irr<-irr-((irr-t)*pv/(pv-pvPrev));
>  >          pvPrev<-pv;
>  >   
>  >  pv<-sum(cashFlow/((1+irr)^(as.numeric(difftime(cfDate,"2010-08-24",units="da
>  >  ys"))/365)))
>  >          print(irr);print(pv)
>  >          }
>  >  }
>  >  
>  >  
>  >  
>  >  
>  >  
>  >  Please consider the environment before printing this e-mail.
>  >  
>  >  	[[alternative HTML version deleted]]
>  >  
>  >  ______________________________________________
>  >  R-help at r-project.org mailing list
>  >  
>  >  PLEASE do read the posting guide 
>  >  and provide commented, minimal, self-contained, reproducible code.
>  >  
>  >  
>  >
>  
>  ______________________________________________
>  R-help at r-project.org mailing list
>  
>  PLEASE do read the posting guide 
>  and provide commented, minimal, self-contained, reproducible code.



More information about the R-help mailing list