[Returnanalytics-commits] r2610 - in pkg/PerformanceAnalytics/sandbox/pulkit: week2/code week3_4/vignette

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sun Jul 21 12:18:49 CEST 2013


Author: pulkit
Date: 2013-07-21 12:18:48 +0200 (Sun, 21 Jul 2013)
New Revision: 2610

Modified:
   pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkPlots.R
   pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkSR.R
   pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/SRIndifferenceCurve.R
   pkg/PerformanceAnalytics/sandbox/pulkit/week3_4/vignette/TriplePenance.Rnw
Log:
changes in SR indifferent curves

Modified: pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkPlots.R
===================================================================
--- pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkPlots.R	2013-07-21 03:53:14 UTC (rev 2609)
+++ pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkPlots.R	2013-07-21 10:18:48 UTC (rev 2610)
@@ -1,6 +1,56 @@
-BenchmarkSRPlots<-function(R=NULL,ylab = NULL,xlab = NULL,lwd = 2,pch = 1,cex = 1,avgSR = NULL,columns = NULL,...){
+#'@title Benchmark Sharpe Ratio Plots
+#'
+#'@description
+#'Benchmark Sharpe Ratio Plots are used to give the relation ship between the
+#'Benchmark Sharpe Ratio and average correlation,average sharpe ratio or the number of #'strategies keeping other parameters constant. Here average Sharpe ratio , average #'correlation stand for the average of all the strategies in the portfolio. The original 
+#'point of the return series is also shown on the plots. 
+#'
+#'@param R an xts, vector, matrix, data frame, timeSeries or zoo object of
+#' asset returns
+#'@param ylab set the y-axis label, as in \code{\link{plot}}
+#'@param xlab set the x-axis label, as in \code{\link{plot}}
+#'@param main set the chart title, as in \code{\link{plot}}
+#'@param element.color set the element.color value as in \code{\link{plot}}
+#'@param lwd set the width of the line, as in \code{\link{plot}}
+#'@param pch set the pch value, as in \code{\link{plot}}
+#'@param cex set the cex value, as in \code{\link{plot}}
+#'@param cex.axis set the cex.axis value, as in \code{\link{plot}}
+#'@param cex.main set the cex.main value, as in \code{\link{plot}}
+#'@param vs The values against which benchmark SR has to be plotted. can be 
+#'"sharpe","correlation" or "strategies"
+#'@param ylim set the ylim value, as in \code{\link{plot}}
+#'@param xlim set the xlim value, as in \code{\link{plot}}
+
+#'@references
+#'Bailey, David H. and Lopez de Prado, Marcos, The Strategy Approval Decision: 
+#'A Sharpe Ratio Indifference Curve Approach (January 2013). Algorithmic Finance, 
+#'Vol. 2, No. 1 (2013).
+#'
+#'@seealso \code{\link{plot}}
+#'@keywords ts multivariate distribution models hplot
+#'@examples
+#'
+#'chart.BenchmarkSR(edhec,vs="strategies")
+#'chart.BenchmarkSR(edhec,vs="sharpe")
+#'@export
+
+chart.BenchmarkSR<-function(R=NULL,main=NULL,ylab = NULL,xlab = NULL,element.color="darkgrey",lwd = 2,pch = 1,cex = 1,cex.axis=0.8,cex.lab = 1,cex.main = 1,vs=c("sharpe","correlation","strategies"),xlim = NULL,ylim = NULL,...){
   
+  # DESCRIPTION:
+  # Draws Benchmark SR vs various variables such as average sharpe , 
+  # average correlation and the number of strategies
   
+  # INPUT:
+  # The Return Series of the portfolio is taken as the input. The Return 
+  # Series can be an xts, vector, matrix, data frame, timeSeries or zoo object of
+  # asset returns.
+  
+  # All other inputs are the same as "plot" and are principally included
+  # so that some sensible defaults could be set.
+  
+  # vs parameter takes the value against which benchmark sr has to be plotted
+  
+  # FUNCTION:
   if(!is.null(R)){
     x = checkData(R)
     columns = ncol(x)
@@ -20,10 +70,67 @@
     }
   }
   corr_avg = corr_avg*2/(columns*(columns-1))
-  
-  rho = seq(0,1,length.out=30)
-  SR_B = avgSR*sqrt(columns/(1+(columns-1)*rho))
-  plot(rho,SR_B,type="l",xlab="Correlation",ylab="Benchmark Sharpe Ratio",main="Benchmark Sharpe Ratio vs Correlation")
-  points(corr_avg[1,1],BenchmarkSR(R),col="blue",pch=10)
-  text(corr_avg[1,1],BenchmarkSR(R),"Original Point",pos=4)
-}
\ No newline at end of file
+  if(vs=="sharpe"){
+    if(is.null(ylab)){
+      ylab = "Benchmark Sharpe Ratio"
+    }
+    if(is.null(xlab)){
+      xlab = "Average Sharpe Ratio"
+    }
+    if(is.null(main)){
+      main = "Benchmark Sharpe Ratio vs Average Sharpe Ratio"
+    }
+    sr = seq(0,1,length.out=30)
+    SR_B = sr*sqrt(columns/(1+(columns-1)*corr_avg[1,1]))
+    plot(sr,SR_B,type="l",xlab=xlab,ylab=ylab,main=main,lwd = lwd,pch=pch,cex = cex,cex.lab = cex.lab)
+    points(avgSR,BenchmarkSR(R),col="blue",pch=10)
+    text(avgSR,BenchmarkSR(R),"Return Series ",pos=4)
+  } 
+  if(vs=="correlation"){
+    
+    if(is.null(ylab)){
+      ylab = "Benchmark Sharpe Ratio"
+    }
+    if(is.null(xlab)){
+      xlab = "Average Correlation"
+    }
+    if(is.null(main)){
+      main = "Benchmark Sharpe Ratio vs Correlation"
+    }
+    rho = seq(0,1,length.out=30)
+    SR_B = avgSR*sqrt(columns/(1+(columns-1)*rho))
+    plot(rho,SR_B,type="l",xlab=xlab,ylab=ylab,main=main,lwd = lwd,pch=pch,cex = cex,cex.lab = cex.lab)
+    points(corr_avg[1,1],BenchmarkSR(R),col="blue",pch=10)
+    text(corr_avg[1,1],BenchmarkSR(R),"Return Series ",pos=4)
+  }
+  if(vs=="strategies"){
+    
+    if(is.null(ylab)){
+      ylab = "Benchmark Sharpe Ratio"
+    }
+    if(is.null(xlab)){
+      xlab = "Number of Strategies"
+    }
+    if(is.null(main)){
+      main = "Benchmark Sharpe Ratio vs Number of Strategies"
+    }
+    n = seq(2,100,length.out=20)
+    SR_B = avgSR*sqrt(n/(1+(n-1)*corr_avg[1,1]))
+    plot(n,SR_B,type="l",xlab=xlab,ylab=ylab,main=main,lwd = lwd,pch=pch,cex = cex,cex.lab = cex.lab)
+    points(columns,BenchmarkSR(R),col="blue",pch=10)
+    text(columns,BenchmarkSR(R),"Return Series ",pos=4)
+  }
+
+}
+
+###############################################################################
+# R (http://r-project.org/) Econometrics for Performance and Risk Analysis
+#
+# Copyright (c) 2004-2013 Peter Carl and Brian G. Peterson
+#
+# This R package is distributed under the terms of the GNU Public License (GPL)
+# for full details see the file COPYING
+#
+# $Id: BenchmarkSRPlots.R $
+#
+###############################################################################
\ No newline at end of file

Modified: pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkSR.R
===================================================================
--- pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkSR.R	2013-07-21 03:53:14 UTC (rev 2609)
+++ pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/BenchmarkSR.R	2013-07-21 10:18:48 UTC (rev 2610)
@@ -11,6 +11,9 @@
 #'@aliases BenchmarkSR
 #'\deqn{SR_B = \bar{SR}\sqrt{\frac{S}{1+(S-1)\bar{\rho}}}}
 #'
+#'Here \eqn{\bar{SR}} is the average SR of the portfolio and \eqn{\bar{\rho}} 
+#'is the average correlation across off-diagonal elements
+#'
 #'@param R a vector, matrix, data frame,timeseries or zoo object of asset returns
 #'
 #'@references
@@ -21,11 +24,20 @@
 #'@examples
 #'
 #'data(edhec)
-#'BenchmarkSR(edhec) #expected 0.2019308
+#'BenchmarkSR(edhec) #expected 0.393797
 #'
 #'@export
 #'
 BenchmarkSR<-function(R){
+  # DESCRIPTION:
+  # Returns the Value of the Benchmark Sharpe Ratio.
+  
+  # INPUT:
+  # The return series of all the series in the portfolio is taken as the input
+  # The return series can be a vector, matrix, data frame,timeseries or zoo 
+  # object of asset returns.
+  
+  # FUNCTION:
   x = checkData(R)
   columns = ncol(x)
   #TODO : What to do if the number of columns is only one ?  
@@ -45,3 +57,14 @@
   SR_Benchmark = sr_avg*sqrt(columns/(1+(columns-1)*corr_avg[1,1]))
   return(SR_Benchmark)
 }
+###############################################################################
+# R (http://r-project.org/) Econometrics for Performance and Risk Analysis
+#
+# Copyright (c) 2004-2013 Peter Carl and Brian G. Peterson
+#
+# This R package is distributed under the terms of the GNU Public License (GPL)
+# for full details see the file COPYING
+#
+# $Id: BenchmarkSR.R $
+#
+###############################################################################
\ No newline at end of file

Modified: pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/SRIndifferenceCurve.R
===================================================================
--- pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/SRIndifferenceCurve.R	2013-07-21 03:53:14 UTC (rev 2609)
+++ pkg/PerformanceAnalytics/sandbox/pulkit/week2/code/SRIndifferenceCurve.R	2013-07-21 10:18:48 UTC (rev 2610)
@@ -3,32 +3,69 @@
 #'
 #'@description
 #'The trade-off between a candidate’s SR and its correlation
-#' to the existing set of strategies, is given by the Sharpe 
-#' ratio indifference curve. It is a plot between the candidate's 
-#' Sharpe Ratio and candidate's average correlation for a given 
-#' portfolio Sharpe Ratio.
+#'to the existing set of strategies, is given by the Sharpe 
+#'ratio indifference curve. It is a plot between the candidate's 
+#'Sharpe Ratio and candidate's average correlation for a given 
+#'portfolio Sharpe Ratio.Portfolio's sharpe Ratio remains constant 
+#'if any strategy from the Sharpe Ratio Indifference Curve is added.
 #' 
 #'The equation for the candidate's average autocorrelation for a given 
 #'sharpe Ratio is given by
 #'
 #'\deqn{\bar{\rho{_s+1}}=\frac{1}{2}\biggl[\frac{\bar{SR}.S+SR_{s+1}^2}{S.SR_B^2}-\frac{S+1}{S}-\bar{rho}{S-1}\biggr]}
 #'
+#'This is the correlation that the candidate's strategy should have with the portfolio
+#'for the Sharpe Ratio of the portfolio to remain constant if this strategy is added.
+#'
 #'@param R an xts, vector, matrix, data frame, timeSeries or zoo object of
 #' asset returns
+#'@param reference.grid if true, draws a grid aligned with the points on the x
+#'and y axes
 #'@param ylab set the y-axis label, as in \code{\link{plot}}
 #'@param xlab set the x-axis label, as in \code{\link{plot}}
+#'@param main set the chart title, as in \code{\link{plot}}
+#'@param element.color set the element.color value as in \code{\link{plot}}
 #'@param lwd set the width of the line, as in \code{\link{plot}}
 #'@param pch set the pch value, as in \code{\link{plot}}
 #'@param cex set the cex value, as in \code{\link{plot}}
+#'@param cex.axis set the cex.axis value, as in \code{\link{plot}}
+#'@param cex.main set the cex.main value, as in \code{\link{plot}}
+#'@param ylim set the ylim value, as in \code{\link{plot}}
+#'@param xlim set the xlim value, as in \code{\link{plot}}
 #'
 #'@references 
 #'Bailey, David H. and Lopez de Prado, Marcos, The Strategy Approval Decision: 
 #'A Sharpe Ratio Indifference Curve Approach (January 2013). Algorithmic Finance, 
 #'Vol. 2, No. 1 (2013).
 #'
-#'
-SRIndifference<-function(R, ylab = NULL,xlab = NULL,lwd = 2,pch = 1,cex = 1,...){
+#'@seealso \code{\link{plot}}
+#'@keywords ts multivariate distribution models hplot
+#'@examples
+#' 
+#'data(edhec)
+#'chart.SRIndifference(edhec)
+#' 
+#'@export 
+
+chart.SRIndifference<-function(R,reference.grid = TRUE, ylab = NULL,xlab = NULL,main = "Sharpe Ratio Indifference Curve",element.color = "darkgrey",lwd = 2,pch = 1,cex = 1,cex.axis = 0.8,cex.lab = 1,cex.main = 1,ylim = NULL,xlim = NULL,...){
   
+  # DESCRIPTION:
+  # Draws the Sharpe Ratio Indifference curve, which  gives us pairs 
+  # of correlation and sharpe ratio of strategies which when added
+  # to the portfolio do not effect the portfolio's Sharpe Ratio.
+  
+  # INPUT:
+  # The Return Series of the portfolio is taken as the input. The Return 
+  # Series can be an xts, vector, matrix, data frame, timeSeries or zoo object of
+  # asset returns.
+  
+  # All other inputs are the same as "plot" and are principally included
+  # so that some sensible defaults could be set.
+  
+  # Output:
+  # Draws the Sharpe Ratio Indifference Curve with some sensible defaults.
+  
+  # FUNCTION:
   x = checkData(R)
   columns = ncol(x)
   #TODO: What to do when the number of columns is 1 ?
@@ -45,7 +82,7 @@
     }
   }
   corr_avg = corr_avg*2/(columns*(columns-1))
-  SR_B = BenchmanrkSR(R)
+  SR_B = BenchmarkSR(R)
   corr_range = seq(-1,1,length.out = 30)
   SR_i = NULL
   for(i in corr_range){
@@ -58,7 +95,23 @@
   if(is.null(xlab)){
     xlab = "Candidate's Strategy's Sharpe Ratio"
   }
-  plot(SR_i,corr_range,type="l",xlab = xlab,ylab = ylab,main="Sharpe Ratio Indifference Curve")
-  #OR we can use ggplot2 for much better plots
-  #qplot(SR_i,corr_range,geom="line",xlab=xlab,ylab=ylab,main="Sharpe Ratio IndifferenceCurve",margins=TRUE,facet="grid")+stat_summary()
+  plot(corr_range~SR_i,type="l",xlab = '',ylab = '',main=main,cex =cex,xlim = xlim,ylim = ylim,pch = pch,lwd = lwd)
+  title(ylab = ylab,cex.lab = cex.lab)
+  title(xlab = xlab,cex.lab = cex.lab)
+  if(reference.grid) {
+    grid(col = element.color)
+    abline(h = 0, col = element.color)
+    abline(v = 0, col = element.color)
+  }
 }
+###############################################################################
+# R (http://r-project.org/) Econometrics for Performance and Risk Analysis
+#
+# Copyright (c) 2004-2013 Peter Carl and Brian G. Peterson
+#
+# This R package is distributed under the terms of the GNU Public License (GPL)
+# for full details see the file COPYING
+#
+# $Id: chart.SRIndifferenceCurve.R $
+#
+###############################################################################
\ No newline at end of file

Modified: pkg/PerformanceAnalytics/sandbox/pulkit/week3_4/vignette/TriplePenance.Rnw
===================================================================
--- pkg/PerformanceAnalytics/sandbox/pulkit/week3_4/vignette/TriplePenance.Rnw	2013-07-21 03:53:14 UTC (rev 2609)
+++ pkg/PerformanceAnalytics/sandbox/pulkit/week3_4/vignette/TriplePenance.Rnw	2013-07-21 10:18:48 UTC (rev 2610)
@@ -49,6 +49,9 @@
 @
 
 
+<<echo=FALSE>>=
+source("../code/TuW.R")
+@
 \section{ Maximum Drawdown }
 Maximum Drawdown tells us Up to how much could a particular strategy lose with a given confidence level ?. This function calculated Maximum Drawdown for two underlying processes normal and autoregressive. For a normal process Maximum Drawdown is given by the formula
 
@@ -101,8 +104,17 @@
 For a Autoregressive process the Time under water is found using the golden section algorithm.
 
 \subsection{Usage}
+<<>>=
+data(edhec)
+TuW(edhec,0.95,type="ar")
+@
 
+The Return Series ,confidence level and the type of distribution is taken as the input. The Return Series can be an xts, vector, matrix, data frame, timeSeries or zoo object of asset returns.
 
+The out is given in the same periodicity as the input series.
 
+\section{ Golden Section Algorithm }
+
+
 \end{document}
 



More information about the Returnanalytics-commits mailing list