sandbox/optimizer.R

# Optimizer Functions

################################################################################
# FUNCTIONS:
#
# BruteForcePortfolios (R,weightgrid,yeargrid)
# BacktestData ()
# Backtest (R,portfolioreturns, yeargrid, cutat=1000000, methods, p, ... )
# weight.grid (columnnames, seqstart=.05, seqend=.25, seqstep=.05)
# maxdrawdown (R)
# cut.returns (R, cutrow, startrow=1)
# weighttest (weightgrid, test=1)
# WeightedPortfolioUtility (R, weightgrid, from, to, methods, p, ...)
# backtestDisplay (R, portfolioreturns, yeargrid, backtestresults, show="Cumulative.Return" )
# MonthlyBacktestResults (R, weightgrid, yeargrid, backtestweights)
#
################################################################################

# Check to see if the required libraries are loaded
if(!require("PerformanceAnalytics", quietly=TRUE)) {
    stop("package", sQuote("PerformanceAnalytics"), "is needed.  Stopping")
}
#source("optim_functions.R")

# ------------------------------------------------------------------------------
cut.returns =
function (R, cutrow, startrow=1)
{   # @author Brian G. Peterson

    # Description:

    # FUNCTION:
    result = R[startrow:cutrow,]

    # Return Value:
    result
}

# ------------------------------------------------------------------------------
weighttest =
function (weightgrid, test=1)
{
    rows=nrow(weightgrid)

    result=NA

    for(row in 1:rows) {
        r = as.vector(weightgrid[row,])
        #if (!is.numeric(r)) stop("The selected row is not numeric")

        if (sum(r) == test) {
            #if (result=NA) {
                #create data.frame
            #    result=data.frame(r=r)
            #} else {
                r=data.frame(r=r)
                result=cbind(result,r)
            #}
        }
    } #end rows loop

    # Return Value:
    result

}

# ------------------------------------------------------------------------------
# @todo: use zoo rollapply in BruteForcePortfolios() fn
#WeightedPortfolioUtility =
WeightedPortfolioUtility =
function (R, weightgrid, from, to,
          methods=c( "PeriodGVaR", "ThreeYrGVaR", "InceptionGVaR", "PeriodmodVaR", "ThreeYrmodVaR", "InceptionmodVaR",
                     "PeriodGES", "ThreeYrGES", "InceptionGES", "PeriodmodES", "ThreeYrmodES", "InceptionmodES",
                     "PeriodStdDev", "ThreeYrStdDev", "InceptionStdDev",
                     "PeriodReturn", "maxdd", "omega" )
          , p=0.95, ... )
{ # @author Brian G. Peterson and Kris Boudt

    # Description:
    # This is the workhorse of the backtest architecture.
    # Any optimization backtesting model must
    #     - create portfolios,
    #     - analyze their returns,
    #     - and allow you to use some metric, function, or algorithm
    #       to analyze the results
    #
    # function takes a set of returns, a set of portfolio weights,
    # and a timeframe to operate within, and generates a set of statistics
    # for every possible weight.
    #
    # When you calculate statistics for all possible weights generated by
    # a brute force method, an estimation method, some function,
    # a regression, etc., you can then run tests against the results "in-sample"
    # to determine which weighting vector you want to use "out-of-sample"
    # in the next rolling period.
    #
    # This function is extremely computationally intensive, because it is doing
    # a lot of things with every single possible weighting vector, so you want
    # to be able to run it and store the results for later analysis.
    # It is best to strike a balance between placing functions in here that
    # you will need to help choose the optimal weighting vector, and be
    # parsimonious, as these calculations may be run tens of thousands of times
    # in any given backtest.  Remember that once you have chosen an optimal
    # portfolio or a sub-set of possible optimal portfolios, you can run more
    # exhaustive analytics on each of your candidates later, rather than on the
    # entire set of all possible portfolios.
    #
    # R             data structure of historical returns
    # weightgrid    each row contains one weighting vector, same number of columns as your returns
    # from          where to cut the beginning of the return stream
    # to            where to cut the end of the return stream
    #
    # @returns      data frame where each row has the same index number as a weighting vector,
    #               and each column is one of your metrics from inside this function
    #
    # @todo don't recalculate if Period and ThreeYr or Inception and ThreeYr are the same

    # Setup:
    # there's a risk here is sampling from weightgrid that
    # your row names and numbers won;t match, need to be careful

    # data type conditionals
    # cut the return series for from:to
    if (class(R) == "timeSeries") {
        R = R@Data
    }

    if (from < 1) from = 1
    if (to > nrow(R)) to = nrow(R)


    if (ncol(weightgrid) != ncol(R)) stop ("The Weighting Vector and Return Collection do not have the same number of Columns.")

    # Compute multivariate moments
    # should probably change this part to use zoo's rollapply to create the various groupings

    threeyrfrom = to - 35; #for monthly data 36-35=1 for three year period
    if (threeyrfrom < 1 ) threeyrfrom = 1

    R.inception = R[1:to , ];
    mu.inception = apply(R.inception,2,'mean');
    sigma.inception = cov(R.inception);
    M3.inception = M3.MM(R.inception);
    M4.inception = M4.MM(R.inception);

    R.period = R[from:to, ];
    mu.period =  apply(R.period,2,'mean');
    sigma.period = cov(R.period);
    M3.period = M3.MM(R.period);
    M4.period = M4.MM(R.period);

    R.3yr = R[ threeyrfrom:to, ];
    mu.3yr = apply(R.3yr,2,'mean');
    sigma.3yr = cov(R.3yr);
    M3.3yr = M3.MM(R.3yr);
    M4.3yr = M4.MM(R.3yr);

    rows=nrow(weightgrid)
    # Function:
    # this outer loop makes me very angry.
    # R seems to hang and never return  on very large matrices or data.frame's
    # to get around this, we subset the data into chunks that R can handle,
    # we then run the inner for loop against these, and reassemble the list
    # into a single structure at the end.
    #
    # if we *must* do this to work around limitations in R, perhaps we can
    # figure out how to examine the length of weightgrid and subset it automatically
    subsetrows= matrix(c(1,31000,31001,62000,62001,rows), nrow=3,byrow=TRUE)
    # subsetrows= matrix(c(1,10,11,20,21,30), nrow=3,byrow=TRUE)
    resultlist=vector("list", 3)
    weightgridsave=weightgrid
    for (srow in 1:3) {
        weightgrid=weightgrid[subsetrows[srow,1]:subsetrows[srow,2],,drop=FALSE]
        result=NULL

    for(row in rownames(weightgrid)) {
        # at some point consider parallelizing this by using a clustered apply
        # to call a sub-function so that this could get distributed
        # to multiple processor cores or threads

        # construct a data structure that holds each result for this row
        resultrow=data.frame(row.names = row)

        w = as.numeric(weightgrid[row,])
        # test each row in the weighting vectors against the right dates in the return collection

       # problem of NAs? Not solved yet !!!!
       # should really solve this by calling checkData in ButeForcePortfolios
       #if (any(is.na(R))) {
       #     print( paste("NA\'s in returns: ",row, " ",w," from ", from) )
       #     #browser()
       #}

        mean.inception = mean.MM( w , mu.inception );
        mean.period = mean.MM( w , mu.period) ;
        mean.3yr = mean.MM( w , mu.3yr ) ;

        for (method in methods) {
            switch(method,
                PeriodStdDev = {
                    # Standard Deviation
                    PeriodStdDev = StdDev.MM(w,sigma=sigma.period)
                    PeriodSRStdDev = mean.period/ PeriodStdDev
                    colnames(PeriodStdDev) = "StdDev.period"
                    colnames(PeriodSRStdDev)="SR.StdDev.period"
                    resultrow= cbind(resultrow,PeriodStdDev,PeriodSRStdDev)
                },
                ThreeYrStdDev = {
                    # Standard Deviation
                    ThreeYrStdDev = StdDev.MM(w,sigma=sigma.3yr)
                    ThreeYrSRStdDev = mean.3yr/ThreeYrStdDev;
                    colnames(ThreeYrStdDev) = "StdDev.3yr"
                    colnames(ThreeYrStdDev) = "SR.StdDev.3yr"
                    resultrow= cbind(resultrow,ThreeYrStdDev,ThreeYrSRStdDev)
                },
                InceptionStdDev = {
                    # Standard Deviation
                    InceptionStdDev = StdDev.MM(w,sigma=sigma.inception)
                    InceptionSRStdDev = mean.inception/InceptionStdDev
                    colnames(InceptionStdDev) = "StdDev.inception"
                    colnames(InceptionSRStdDev) = "SR.StdDev.inception"
                    resultrow= cbind(resultrow,InceptionStdDev, InceptionSRStdDev)
                },
                PeriodGVaR = {
                    PeriodGVaR = GVaR.MM(w=w, mu=mu.period, sigma = sigma.period, p=p )
                    PeriodSRGVaR = mean.period/PeriodGVaR
                    colnames(PeriodGVaR)="GVaR.period"
                    colnames(PeriodSRGVaR)="SR.GVaR.period"
                    resultrow= cbind(resultrow,PeriodGVaR,PeriodSRGVaR)
                },
                ThreeYrGVaR = {
                    ThreeYrGVaR = GVaR.MM(w=w, mu=mu.3yr, sigma = sigma.3yr, p=p )
                    ThreeYrSRGVaR =  mean.3yr/ThreeYrGVaR
                    colnames(ThreeYrGVaR)="GVaR.3yr"
                    colnames(ThreeYrSRGVaR)="SR.GVaR.3yr"
                    resultrow= cbind(resultrow,ThreeYrGVaR,ThreeYrSRGVaR)
                },
                InceptionGVaR = {
                    InceptionGVaR = GVaR.MM(w=w, mu=mu.inception, sigma = sigma.inception, p=p )
                    InceptionSRGVaR = mean.inception/InceptionGVaR
                    colnames(InceptionGVaR)="GVaR.inception"
                    colnames(InceptionSRGVaR)="SR.GVaR.inception"
                    resultrow= cbind(resultrow,InceptionGVaR,InceptionSRGVaR)
                },
                PeriodmodVaR = {
                    PeriodmodVaR = mVaR.MM(w=w, mu=mu.period, sigma = sigma.period, M3=M3.period , M4 =M4.period , p=p )
                    PeriodSRmodVaR = mean.period/PeriodmodVaR
                    colnames(PeriodmodVaR)="modVaR.period"
                    colnames(PeriodSRmodVaR)="SR.modVaR.period"
                    resultrow= cbind(resultrow,PeriodmodVaR,PeriodSRmodVaR)
                },
                InceptionmodVaR = {
                    InceptionmodVaR = mVaR.MM(w=w, mu=mu.inception, sigma = sigma.inception, M3=M3.inception , M4 =M4.inception , p=p )
                    InceptionSRmodVaR = mean.inception/InceptionmodVaR
                    colnames(InceptionmodVaR)="modVaR.inception"
                    colnames(InceptionSRmodVaR)="SR.modVaR.inception"
                    resultrow= cbind(resultrow,InceptionmodVaR,InceptionSRmodVaR)
                },
                ThreeYrmodVaR = {
                    ThreeYrmodVaR = mVaR.MM(w=w, mu=mu.3yr, sigma = sigma.3yr, M3=M3.3yr , M4 =M4.3yr, p=p )
                    ThreeYrSRmodVaR = mean.3yr/ThreeYrmodVaR
                    colnames(ThreeYrmodVaR)="modVaR.3yr"
                    colnames(ThreeYrSRmodVaR)="SR.modVaR.3yr"
                    resultrow= cbind(resultrow,ThreeYrmodVaR,ThreeYrSRmodVaR)
                },
                InceptionGES = {
                    InceptionGES = GES.MM(w=w, mu=mu.inception, sigma = sigma.inception, p=p )
                    InceptionSRGES = mean.inception/InceptionGES
                    colnames(InceptionGES)="GES.inception"
                    colnames(InceptionSRGES)="SR.GES.inception"
                    resultrow= cbind(resultrow,InceptionGES,InceptionSRGES)
                },
                PeriodGES = {
                    PeriodGES = GES.MM(w=w, mu=mu.period, sigma = sigma.period, p=p )
                    PeriodSRGES =  mean.period/PeriodGES
                    colnames(PeriodGES)="GES.period"
                    colnames(PeriodSRGES)="SR.GES.period"
                    resultrow= cbind(resultrow,PeriodGES,PeriodSRGES)
                },
                ThreeYrGES = {
                    ThreeYrGES = GES.MM(w=w, mu=mu.3yr, sigma = sigma.3yr, p=p )
                    ThreeYrSRGES = mean.3yr/ThreeYrGES
                    colnames(ThreeYrGES)="GES.3yr"
                    colnames(ThreeYrSRGES)="SR.GES.3yr"
                    resultrow= cbind(resultrow,ThreeYrGES,ThreeYrSRGES)
                },
                PeriodmodES = {
                    PeriodmodES = mES.MM(w=w, mu=mu.period, sigma = sigma.period, M3=M3.period , M4 =M4.period , p=p )
                    PeriodSRmodES =  mean.period/PeriodmodES
                    colnames(PeriodmodES)="modES.period"
                    colnames(PeriodSRmodES)="SR.modES.period"
                    resultrow= cbind(resultrow,PeriodmodES,PeriodSRmodES)
                },
                ThreeYrmodES = {
                    ThreeYrmodES = mES.MM(w=w, mu=mu.3yr, sigma = sigma.3yr, M3=M3.3yr , M4 =M4.3yr , p=p )
                    ThreeYrSRmodES = mean.3yr/ThreeYrmodES
                    colnames(ThreeYrmodES)="modES.3yr"
                    colnames(ThreeYrSRmodES)="SR.modES.3yr"
                    resultrow= cbind(resultrow,ThreeYrmodES,ThreeYrSRmodES)
                },
                InceptionmodES = {
                    InceptionmodES = mES.MM(w=w, mu=mu.inception, sigma = sigma.inception, M3=M3.inception , M4 =M4.inception, p=p )
                    InceptionSRmodES = mean.inception/InceptionmodES
                    colnames(InceptionmodES)="modES.inception"
                    colnames(InceptionSRmodES)="SR.modES.inception"
                    resultrow= cbind(resultrow,InceptionmodES,InceptionSRmodES)
                }
                # @todo put Return.portfolio, maxdrawdown, omega back, think about others
            )#end switch function
        }# end loop over methods

        if (is.null(result)){
               result=matrix(nrow=nrow(weightgrid),ncol=ncol(resultrow),byrow=TRUE)
               rownames(result)=rownames(weightgrid)
               colnames(result)=colnames(resultrow)
        }

        # print( paste("Completed row: ",rownames(resultrow),":",date()) )
        # then rbind the rows
        # result    = rbind(result,resultrow)
        result[as.character(row),]=as.matrix(resultrow)

    } #end rows loop
          resultlist[[srow]] <- result
          weightgrid=weightgridsave
          print(paste("Row ",subsetrows[srow,2]," completed ",date()))
    } #end subset loop

    result=rbind(resultlist[[1]],resultlist[[2]],resultlist[[3]])

    # Return Value:
    result

}


# ------------------------------------------------------------------------------
# @todo: use zoo rollapply in BruteForcePortfolios() fn
BruteForcePortfolios =
function(R,weightgrid,yeargrid,
          methods=c( "PeriodGVaR", "ThreeYrGVaR", "InceptionGVaR", "PeriodmodVaR", "ThreeYrmodVaR", "InceptionmodVaR",
                     "PeriodGES", "ThreeYrGES", "InceptionGES", "PeriodmodES", "ThreeYrmodES", "InceptionmodES",
                     "maxdd", "omega", "PeriodStdDev", "ThreeYrStdDev", "InceptionStdDev" )
         , p=0.95, ...
        )
{ # @author Brian G. Peterson

    # Description:
    #
    # Performs the looping and storage of the base analytics for your series
    # of possible portfolios.  I've titled the third parameter 'yeargrid',
    # but it is really a 'rolling window grid', although these will often be years.
    # We slice the computation into these years or rolling periods,
    # and store the results separately, because each of these rolling periods will
    # have one solution for each possible weighting vector.  By generating them and
    # storing them for all weighting vectors in every period, you can do all the hard
    # computational work in one pass, and then reuse the data set over and over again
    # in multiple analytic tests, methods, or hypotheses for choosing in-sample results
    # to use as out-of-sample weights.
    #
    # @todo add optional subdirectory tp keep different backtests apart
    #
    # R                 data frame of historical returns
    #
    # weightgrid        each row contains one weighting vector, same number of columns as your returns
    #
    # yeargrid          list of from/to vectors for the periods we want to backtest over
    #
    # Return:
    # portfolioreturns  list of data frames of set of returns for all possible portfolios
    #                   (output of BruteForcePortfolios function)

    # Setup:
    rows=nrow(yeargrid)

    # Function:
    print( paste("Started:",date()) )
    for (rnum in 1:rows) {
        row = yeargrid[rnum,]
        yearname=rownames(row)
        from = row [,1]
        to   = row [,2]

        if (   1  > from ) from = 1
        if ( rows > to   ) to   = rows

        # construct a data structure that holds each result for this year
        resultarray = WeightedPortfolioUtility(R, weightgrid, from, to, methods=methods, p=p, ...=...)
        # at some point parallelize the call to WeightedPortfolioUtility by using a clustered apply
        # to call WeightedPortfolioUtility so that this could get distributed
        # to multiple processor cores or threads

        # then write a CSV
        write.table(resultarray, file = paste(yearname,".csv",sep=""),
            append = FALSE, quote = TRUE, sep = ",",
            eol = "\n", na = "NA", dec = ".", row.names = TRUE,
            col.names = TRUE, qmethod = "escape")

        print( paste("Completed",yearname,":",date()) )
        # print(resultarray)
    }  # end row loop
}

# ------------------------------------------------------------------------------
BacktestData =
function(yeargrid)
{ # @author Brian G. Peterson

    # Description:
    #
    # load the data into a list suitable for use by Backtest and BacktestDisplay functions
    # use the yeargrid used by BruteForcePortfolios to figure out which files to load
    #
    # @todo add optional subdirectory to keep different backtests apart
    #
    # yeargrid          list of from/to vectors for the periods we've run the backtest over
    #                   yeargrid will have one row for the last out of sample year,
    #                   which is not calculated by BruteForcePortfolios

    # Function:
    rows=nrow(yeargrid)-1 # take out the out of sample year, for which there is no data

    for (rnum in 1:rows) {
        row = yeargrid[rnum,]
        yearname=rownames(row)
        # print(yearname)
        currentyeardata  = read.table(paste(yearname,".csv",sep=""),header=TRUE, row.names = 1,sep = ",")
        if (rnum==1) {
            #create e,ty list, as c() doesn't work the way you would expect with a list
            result=vector("list")
        }

        #assign each year into the list using the yearname as the index
        result[[yearname]]=currentyeardata

    }
    names(result) = t(rownames(yeargrid[1:rows,]))

    #Return:
    result
}

# ------------------------------------------------------------------------------
Backtest =
function(R,bfresults, yeargrid, cutat=1000000, benchmarkreturns )
{
    # Description:
    #
    # complete brute force hackjob to get out of sample results
    #
    # Given a set of historical returns R, and a set of portfolio returns calculated from
    # the BruteForcePortfolios function, we can now apply several utility functions to
    # find the best portfolio out of the universe of all sample portfolios.
    #
    # Basically, we find an in-sample solution to each utility function, and store the
    # weighting vector for that portfolio as our strategic weight for use out of sample.
    # by testing several utility functions, we can examine the models for bias, and determine
    # which utility function produces the most acceptable out of sample results.
    #
    # R                 data frame of historical returns
    #
    # bfresults         list of data frames of set of utility fn results for all possible portfolios
    #                   (output of BruteForcePortfolios function)
    #
    # yeargrid          list of from/to vectors for the periods we want to backtest over
    #
    # cutat             numerical index to stop comparing the portfolioreturns at.
    #                   used to slice the weighted returns at particular weight
    #
    # benchmarkreturns  return vector for benchmark, should match the dates on
    #                   the in-sample portfolio returns


    # Setup:
    rows=nrow(yeargrid-1)

    benchmarkreturns = as.vector(benchmarkreturns)

    # construct a matrix for the results that's the same size and labels as the input lists
    result=matrix(nrow=nrow(yeargrid[-1,]),ncol=ncol(bfresults[[1]]))
    rownames(result)=rownames(yeargrid[-1,])
    colnames(result)=colnames(bfresults[[1]])
    colns= colnames(bfresults[[1]])
    portfoliorows=nrow(bfresults[[1]])
    if (cutat<portfoliorows) {
        portfoliorows=cutat
    }

    # Function:
    for (rnum in 1:(rows-1)) {
        insample    = yeargrid[rnum,]
        outofsample = yeargrid[rnum+1,]
        yearname    = rownames(insample)
        outname     = rownames(outofsample)
        inresults   = bfresults[[yearname]][1:portfoliorows,]

        #Check Utility fn for insample , and apply to out of sample row
        print(paste("Starting",yearname,date()))
        for (coln in colns) {
            ##################################
            # Risk/Reward maximization utility functions
            # for utility function
            # w' = max(meanreturn/riskmeasure)
            #
            # These are the Sharpe Ratio and modified Sharpe Ratio methods
            #
            # These utility functions are called "Constant Relative Risk Aversion (CRRA)" (verify this!)
            ##################################
            for (maxmethod in c("SR.StdDev.period", "SR.StdDev.3yr", "SR.StdDev.inception",
                                "SR.GVaR.period", "SR.GVaR.3yr", "SR.GVaR.inception",
                                "SR.modVaR.period", "SR.modVaR.inception", "SR.modVaR.3yr",
                                "SR.GES.inception", "SR.GES.period", "SR.GES.3yr",
                                "SR.modES.period", "SR.modES.3yr", "SR.modES.inception")){
                if (maxmethod==coln){
                    # return the max of the BF in-sample results for that column
                    result[outname,coln]= rownames(inresults[which.max(inresults[1:portfoliorows,coln]),])
                }
            } #end maxmethod

            ##################################
            # Risk Reduction utility functions
            # for utility function
            # w' = min(riskmeasure)
            #
            # These utility functions are called "Constant Absolute Risk Aversion (CARA)"
            ##################################
            for (minmethod in c("StdDev.period", "StdDev.3yr", "StdDev.inception",
                                "GVaR.period", "GVaR.3yr", "GVaR.inception",
                                "modVaR.period", "modVaR.inception", "modVaR.3yr",
                                "GES.inception", "GES.period", "GES.3yr",
                                "modES.period", "modES.3yr", "modES.inception")){
                if (minmethod==coln){
                   # return the min of the BF in-sample results for that column
                    result[outname,coln]= rownames(inresults[which.min(inresults[1:portfoliorows,coln]),])
                }
            } #end minmethod
        } # end columns loop

        print(paste("Completed",yearname,date()))

        # add Equalweighted
        # EqualWeighted = 1

        #         ##################################
        #         # Risk Reduction utility functions
        #         # for utility function
        #         # w' = min(VaR.CornishFisher(p=0.95))
        #         minmodVaR  = which.min(portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.period"])
        #         #minmodVaRi = which.min(portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.inception"])
        #         minmodVaR3yr  = which.min(portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.3yr"])
        #
        #         # for utility function
        #         # w' = max(return/VaR.CornishFisher) for both VaR.CornishFisher.period and VaR.CornishFisher.inception
        #         #SharpeRatio.modified  = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]/portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.period"])
        #         SharpeRatio.modified3yr  = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]/portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.3yr"])
        #         #SharpeRatio.modifiedi = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]/portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.inception"])
        #
        #         # for utility function
        #         # w' = max(return/Max.Drawdown)
        #         ReturnOverDrawdown = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]/portfolioreturns[[yearname]][1:portfoliorows,"Max.Drawdown"])
        #
        #         # for utility function
        #         # w' = max(return)
        #         maxReturn = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"])
        #
        #         # for utility function
        #         # w' = min(VaR.CornishFisher(p=0.95)) such that return is greater than the benchmark
        #         minVaRretoverBM = which.min(portfolioreturns[[yearname]][which(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]>=Return.cumulative(benchmarkreturns[infrom:into])),"VaR.CornishFisher.period"])
        #         if (length(minVaRretoverBM)==0) { minVaRretoverBM = maxReturn }
        #
        #         #for utility function
        #         #w' = max(return) such that VaR.CornishFisher is less than VaR.CornishFisher(benchmark)
        #         maxmodVaRltBM=which.max(portfolioreturns[[yearname]][which(portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.period"]<VaR.CornishFisher(benchmarkreturns[infrom:into],p=0.95)),"Cumulative.Return"])
        #         if (length(maxmodVaRltBM)==0) { maxmodVaRltBM = 1 }
        #
        #         #add utility functions tor Equal weighted portfolio
        #         # for utility function
        #         # w' = min(VaR.CornishFisher(p=0.95)) such that return is greater than equal weighted portfolio
        #         minVaRretoverEW = which.min(portfolioreturns[[yearname]][which(portfolioreturns[[yearname]][1:portfoliorows,"Cumulative.Return"]>=portfolioreturns[[yearname]][1,"Cumulative.Return"]),"VaR.CornishFisher.period"])
        #         if (length(minVaRretoverEW)==0) { minVaRretoverEW = 1 }
        #
        #         #for utility function
        #         #w' = max(return) such that VaR.CornishFisher is less than VaR.CornishFisher(equal weighted)
        #         maxmodVaRltEW=which.max(portfolioreturns[[yearname]][which(portfolioreturns[[yearname]][1:portfoliorows,"VaR.CornishFisher.period"]<portfolioreturns[[yearname]][1,"Cumulative.Return"]),"Cumulative.Return"])
        #         if (length(maxmodVaRltEW)==0) { maxmodVaRltEW = NA }
        #
        #         #for utility function
        #         #w' = max(omega)
        #         maxOmega = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Omega"])
        #
        #         #for utility function
        #         #w' = max(Sharpe.period)
        #         maxPeriodSharpe = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Sharpe.period"])
        #
        #         #for utility function
        #         #w' = max(Sharpe.3.yr)
        #         max3yrSharpe = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Sharpe.3.yr"])
        #
        #         #for utility function
        #         #w' = max(Sharpe.inception)
        #         #maxInceptionSharpe = which.max(portfolioreturns[[yearname]][1:portfoliorows,"Sharpe.inception"])
        #
        #
        #         ########## end of utility functions ##########
        #         # construct a data structure that holds each result for this row
        #         if (rnum==2) {
        #                 #create data.frame
        #                 result=data.frame()
        #                 resultrow=data.frame()
        #         }
        #         # first cbind the columns
        #         resultrow = cbind(EqualWeighted, minmodVaR, minmodVaR3yr, SharpeRatio.modified3yr, ReturnOverDrawdown, maxReturn,
        #                            minVaRretoverBM, maxmodVaRltBM, minVaRretoverEW, maxmodVaRltEW,
        #                            maxPeriodSharpe, max3yrSharpe, maxOmega )
        #
        #         rownames(resultrow) = outname
        #
        #         # then rbind the rows
        #         result    = rbind(result,resultrow)
        #         # print(resultarray)

    }  # end row loop

    # Result:
    result
}

# ------------------------------------------------------------------------------
BacktestDisplay =
function (R, bfresults, yeargrid, backtestresults, benchmarkreturns )
{ # a function by Brian G. Peterson

    # Description:
    # This function lets us use the output of the Backtest() function to do some
    # comparative analysis of how each utility function performed out of sample.
    # It takes as input all the component parts, and shows a single summary statistic
    # for each out of sample period for each utility function.  Periods are rows,
    # utility functions are columns in the output.
    # Eventually, we'll want to make this more sophisticated, and return a
    # data structure with *all* the summary statistics for each out-of-sample portfolio,
    # but this works for now.
    #
    # R                 data frame of historical returns
    #
    # bfresults      list of data frames of set of returns for all possible portfolios
    #                   (output of BruteForcePortfolios function)
    #
    # yeargrid          list of from/to vectors for the periods we've run the backtest over
    #                   yeargrid will have one row for the last out of sample year,
    #                   which is not calculated by BruteForcePortfolios
    #
    # weightgrid        each row contains one weighting vector, same number of columns as your returns
    #
    # backtestresults   data frame of set of weighting vectors for each
    #                   utility function in each year/period
    #                   (output of Backtest function)
    #
    # benchmarkreturns  return vector for benchmark, should match the dates on
    #                   the in-sample portfolio returns


    cols = ncol(backtestresults) # get the number of utility functions

    # add column for equal weighted portfolio in backtestresults
    # probably rep 1 for number of rows, and cbind
    equalcol= t(t(rep(1,nrow(backtestresults))))
    colnames(equalcol)="Equal.Weighted"
    backtestresults=cbind(backtestresults,as.matrix(equalcol))

    result=vector("list")

    # Function:

    for (row in 1:(nrow(backtestresults)-1)){
        yearrow   = backtestresults[row,,drop=FALSE]
        from      = yeargrid [row,1]
        to        = yeargrid [row,2]
        yearname  = rownames(backtestresults[row,,drop=F])

        # print(rownames(backtestresults[row,,drop=FALSE]))

        resultcols = ncol(backtestresults)+2
        resultmatrix=matrix(nrow=ncol(backtestresults),ncol=resultcols,byrow=TRUE )
        colnames(resultmatrix)=c("Return.Portfolio","skewness","kurtosis",colnames(backtestresults)[-(resultcols-2)])
        rownames(resultmatrix)=colnames(backtestresults)

        for (col in 1:ncol(backtestresults)){
            tcols=resultcols-3
            targetportfolio= backtestresults[row,col]
            resultmatrix[col,4:resultcols]=as.matrix(bfresults[[yearname]][targetportfolio,1:(resultcols-3)])
            # calc Return of the portfolio using Portfolio.Return function
            pwealth=Return.portfolio(R[from:to,], weights=weightgrid[targetportfolio,], wealth.index = TRUE)
            totalreturn=pwealth[length(pwealth)]-1
            pwealth=rbind(1,pwealth)
            preturn=t(diff(log(pwealth)))
            # calc skewness
            pskew=skewness(as.vector(preturn))[1]
            # calc kurtosis
            pkurt=kurtosis(as.vector(preturn))[1]
            resultmatrix[col,1]=totalreturn
            resultmatrix[col,2]=pskew
            resultmatrix[col,3]=pkurt
        }

        # @todo add row for benchmark portfolios
        # Call WeightedPortfolioUtility with weight of 1?

        #browser()
        result[[yearname]]=resultmatrix
    }

    #Return:
    result

}

# ------------------------------------------------------------------------------
BacktestWeightDisplay =
function(backtestresults, weightgrid)
{ # @author Brian G. Peterson

    # Description:
    # Display the weights chosen for each year/period for each utility function.
    #
    # backtestresults   data frame of set of weighting vectors for each
    #                   utility function in each year/period
    #                   (output of Backtest function)
    #
    # weightgrid        each row contains one weighting vector,
    #                   same number of columns as your returns
    #                   you probably want to have the column names of the weightgrid match your asset names
    #
    # yeargrid          list of from/to vectors for the periods we've run the backtest over
    #                   yeargrid will have one row for the last out of sample year,
    #                   which is not calculated by BruteForcePortfolios
    #
    # Return:
    # list of years/periods with each period containing a data frame of weights by utiltiy function

    # Setup:

    cols = ncol(backtestresults) # get the number of utility functions

    result=vector("list")

    # Function:

    for (col in 1:ncol(backtestresults)){
        # we're looping on each column in the backtest results (objective functions)
        resultmatrix=matrix(nrow=ncol(weightgrid),ncol=nrow(backtestresults),byrow=TRUE )
        colnames(resultmatrix)=rownames(backtestresults) # years
        rownames(resultmatrix)=colnames(weightgrid)      # instruments
        for (row in 1:nrow(backtestresults)){
            # now loop on years
            resultmatrix[1:ncol(weightgrid),row]=t(weightgrid[backtestresults[row,col],])
        }
        objname=colnames(backtestresults[,col,drop=F])
        #browser()
        result[[objname]]=resultmatrix
    }

    # @todo put a method in here or something to let the user decide how to arrange
    # arrange list by years with rows as objective functions and columns as instruments
    #     for (row in 1:nrow(backtestresults)){
    #         # print(rownames(backtestresults[row,,drop=FALSE]))
    #         resultmatrix=matrix(nrow=ncol(backtestresults),ncol=ncol(weightgrid),byrow=TRUE )
    #         colnames(resultmatrix)=colnames(weightgrid)
    #         rownames(resultmatrix)=colnames(backtestresults)
    #         for (col in 1:ncol(backtestresults)){
    #             resultmatrix[col,1:ncol(weightgrid)]=t(weightgrid[backtestresults[row,col],])
    #         }
    #         yearname=rownames(backtestresults[row,,drop=F])
    #         # browser()
    #         result[[yearname]]=resultmatrix
    #     }

    #Return:
    result
}


# ------------------------------------------------------------------------------
#MonthlyBacktestResults =
# use pfolioReturn(returnarray,weightingvector) from fPortfolio
MonthlyBacktestResults =
function (R, weightgrid, yeargrid, backtestresults)
{ # @author Brian G. Peterson

    # R                 data structure of component returns
    #
    # weightgrid        each row contains one weighting vector, same number of columns as your returns
    #
    # yeargrid          list of from/to vectors for the periods we want to backtest over
    #
    # backtestresults   data frame of set of weighting vectors for each
    #                   utility function in each year/period
    #                   (output of Backtest function)

    # Setup:
    result=NULL
    resultcols=NULL

    # data type conditionals
    # cut the return series for from:to
    if (class(R) == "timeSeries") {
        R = R@Data
    } else {
        R = R
    }

    if (ncol(weightgrid) != ncol(R)) stop ("The Weighting Vector and Return Collection do not have the same number of Columns.")

    # add column for equal weighted portfolio in backtestresults
    # probably rep 1 for number of rows, and cbind
    equalcol= t(t(rep(1,nrow(backtestresults))))
    colnames(equalcol)="Equal.Weighted"
    backtestresults=cbind(backtestresults,as.matrix(equalcol))

    result=data.frame()
    for (row in 1:(nrow(backtestresults)-1)){
        # ok, we're looping on year.
        # for each year, we need to apply the weights in our backtest results to the portfolio and get a monthly return
        yearrow   = backtestresults[row,,drop=FALSE]
        yearname  = rownames(backtestresults[row,,drop=F])
        from      = yeargrid [yearname,1]
        to        = yeargrid [yearname,2]
        print(paste("Starting",yearname,date()))
        resultcols=NULL

        for (col in 1:ncol(backtestresults)){
            # look up the weighting vector of the target portfolio
            targetportfolio= backtestresults[row,col]
            # calc Return of the portfolio using Portfolio.Return function
            preturn=Return.portfolio(R[from:to,], weights=weightgrid[targetportfolio,], wealth.index = FALSE,method="compound")
            if (col==1) {
                #create data.frame
                resultcols=preturn
            } else {
                resultcols=cbind(resultcols,preturn)
            }
            # @todo add col for benchmark portfolios
        }
        if (row==1) {
            #create data.frame
            result=resultcols
        } else {
            result=rbind(result,resultcols)
        }
        print(paste("Ending",yearname,date()))
    }

    colnames(result)=colnames(backtestresults)

    # Return Value:
    result

}

# Return.portfolio.multiweight <- function (R, weights, yeargrid, ...){
#     result=data.frame()
# 
#     weights=checkData(weights,method="matrix")
# 
#     # take only the first method
# #     method = method[1]
# 
#     # then loop:
#     for (row in 1:nrow(yeargrid)){
#         from =yeargrid[row,1]
#         to = yeargrid[row,2]
#         if(row==1){ startingwealth=1 }
#         resultreturns=Return.portfolio(R[from:to,],weights=t(weights[row,]), startingwealth=startingwealth, ...=...)
#         startingwealth=resultreturns[nrow(resultreturns),"portfolio.wealthindex"]
#         # the [,-1] takes out the weighted returns, which you don't care
#         # about for contribution, although you may care about it for
#         # graphing, and want to pull it into another var
# 
#         result=rbind(result,resultreturns)
#     }
#     result
# }
# # ------------------------------------------------------------------------------
# # Return.portfolio - replaces RMetrics pfolioReturn fn
# # move this function and the pfolioReturn wrapper into Performanceanalytics and remove from this file
# 
# Return.portfolio <- function (R, weights=NULL, wealth.index = FALSE, contribution=FALSE, method = c("compound","simple"), startingwealth=1)
# {   # @author Brian G. Peterson
# 
#     # Function to calculate weighted portfolio returns
#     #
#     # R                 data structure of component returns
#     #
#     # weights           usually a numeric vector which has the length of the number
#     #                   of  assets. The weights measures the normalized weights of
#     #                   the  individual assets. By default 'NULL', then an equally
#     #                   weighted set of assets is assumed.
#     #
#     # method:           "simple", "compound"
#     #
#     # wealth.index      if wealth.index is TRUE, return a wealth index, if false, return a return vector for each period
#     #
#     # contribution      if contribution is TRUE, add the weighted return contributed by the asset in this period
#     #
#     # @todo method param doesn't really do anything right now.  the calculation of the price series would be different for simple than compound
#     # @todo add contribution
# 
#     # Setup:
#     R=checkData(R,method="zoo")
# 
#     # take only the first method
#     method = method[1]
# 
#     if (is.null(weights)){
#         # set up an equal weighted portfolio
#         weights = t(rep(1/ncol(R), ncol(R)))
#     }
# 
#     if (ncol(weights) != ncol(R)) stop ("The Weighting Vector and Return Collection do not have the same number of Columns.")
# 
#     #Function:
# 
# 
# #    if(method=="compound") {
#         # construct the wealth index of unweighted assets
#         wealthindex.assets=cumprod(startingwealth+R)
# 
#         # I don't currently think that the weighted wealth index is the correct route
#         # I'll uncomment this and leave it in here so that we can compare
#         # build a structure for our weighted results
#         wealthindex.weighted = matrix(nrow=nrow(R),ncol=ncol(R))
#         colnames(wealthindex.weighted)=colnames(wealthindex.assets)
#         rownames(wealthindex.weighted)=rownames(wealthindex.assets)
# 
#         # weight the results
#         for (col in 1:ncol(weights)){
#             wealthindex.weighted[,col]=weights[,col]*wealthindex.assets[,col]
#         }
#         wealthindex=apply(wealthindex.weighted,1,sum)
# 
#         # weighted cumulative returns
#         weightedcumcont=t(apply (wealthindex.assets,1, function(x,weights){ as.vector((x-startingwealth)* weights)},weights=weights))
#         weightedreturns=diff(rbind(0,weightedcumcont))
#         colnames(weightedreturns)=colnames(wealthindex.assets)
#         #browser()
#         wealthindex=matrix(cumprod(startingwealth + as.matrix(apply(weightedreturns,1, sum), ncol = 1)),ncol=1)
#         # or, the equivalent
#         #wealthindex=matrix(startingwealth+apply(weightedcumcont,1,sum),ncol=1)
# #   }
# 
#     if(method=="simple"){
#         # stop("Calculating wealth index for simple returns not yet supported.")
#         #weighted simple returns
#         # probably need to add 1 to the column before doing this
#         weightedreturns=Return.calculate(wealthindex,method="simple")
#     }
# 
#         # uncomment this to test
#         #browser()
# 
#     if (!wealth.index){
#         result=as.matrix(apply(weightedreturns,1,sum),ncol=1)
#         colnames(result)="portfolio.returns"
#     } else {
#         # stop("This is broken right now.  Calculate your wealth index from the return series.")
#         result=wealthindex
#         colnames(result)="portfolio.wealthindex"
#     }
# 
#     if (contribution==TRUE){
#         # show the contribution to the returns in each period.
#         result=cbind(weightedreturns,result)
#     }
# 
#     result
# } # end function Return.portfolio
# 
# pfolioReturn <- function (x, weights=NULL, ...)
# {   # @author Brian G. Peterson
#     # pfolioReturn wrapper - replaces RMetrics pfolioReturn fn
# 
#     Return.portfolio(R=x, weights=weights, ...=...)
# }
###############################################################################
# R (http://r-project.org/) Numeric Methods for Optimization of Portfolios
#
# Copyright (c) 2004-2014 Kris Boudt, Peter Carl and Brian G. Peterson
#
# This library is distributed under the terms of the GNU Public License (GPL)
# for full details see the file COPYING
#
# $Id$
#
###############################################################################
# $Log: not supported by cvs2svn $
# Revision 1.85  2009-09-22 21:21:37  peter
# - added licensing details
#
# Revision 1.84  2008-01-31 17:31:00  brian
# - add startingweight to contribution calc
#
# Revision 1.83  2008/01/31 12:21:50  brian
# - add wealth index calcs back in
# - uncomment the old wealthindex.weighted for comparison
#
# Revision 1.82  2008/01/31 04:16:24  peter
# - removed method line from Return.portfolio.multiweight
#
# Revision 1.81  2008/01/31 02:10:32  brian
# - pass ... instead of method argument in Return.portfolio.multiweights
#
# Revision 1.80  2008/01/31 01:23:00  brian
# - add as.vector in method simle for weights in Return.portfolio
#   - **not sure the simple method works properly**
#
# Revision 1.79  2008/01/31 01:15:07  brian
# - add method argument to Return.portfolio.multiweights
#
# Revision 1.78  2008/01/31 00:48:49  brian
# - add new function Return.portfolio.multiweight
#
# Revision 1.77  2008/01/30 23:41:54  brian
# - add contributions as output again to Return.portfolio
#
# Revision 1.76  2008/01/30 23:34:00  brian
# - add rowname for cumulative returns
#
# Revision 1.74  2008/01/29 20:16:21  brian
# - fixed, tested contribution option for Return.portfolio fn
#
# Revision 1.73  2008/01/29 18:23:20  brian
# - add contribution to Return.portfolio
#
# Revision 1.72  2008/01/29 02:59:24  brian
# - comment browser() command
#
# Revision 1.71  2008/01/29 02:58:30  brian
# - reverse output of BacktestWeightDisplay fn to make it easier to graph weights.
#
# Revision 1.70  2008/01/25 02:14:06  brian
# - fix errors in data frrame/matrix handling in Return generating functions
#
# Revision 1.69  2008/01/25 01:28:54  brian
# - complete function MonthlyBacktestResults
#
# Revision 1.68  2008/01/24 23:59:38  brian
# - add Return, skewness, kurtosis to BacktestDisplay
# - always display results for equal weighted portfolio
#
# Revision 1.67  2008/01/24 22:10:01  brian
# - working version of BacktestDisplay fn
#   - still needs Return, skewness, kurtosis
#
# Revision 1.66  2008/01/24 01:51:12  brian
# - resolve conflicts from editing in two directories
#
# Revision 1.65  2008/01/24 01:48:29  brian
# - lay groundwork for rewriting BacktestDisplay fn
#
# Revision 1.64  2008/01/24 00:13:43  brian
# - rename pfolioReturn fn Return.portfolio
# - create wrapper for RMetrics pfolioReturn fn for compatibility
# - add notes about contribution of assets to portfolio return
#
# Revision 1.63  2008/01/23 21:48:35  brian
# - move rbind outside inner if statements to remove dup code
#
# Revision 1.62  2008/01/23 21:46:44  brian
# - update to not lose first period in return stream
# - add column names to make clear what the output is
#
# Revision 1.60 2008-01-23 05:34 brian
# - new version of BacktestWeightDisplay works with output of Backtest fn
#
# Revision 1.61  2008/01/23 20:32:52  brian
# - replacement pfolioReturn function to calculate weighted returns
#
# Revision 1.59  2008/01/23 11:04:17  brian
# - fix 3yr/period confusion in two ThreeYr utility functions in WeightedPortfolios
#
# Revision 1.58  2008/01/22 20:33:49  brian
# - update three yr to to-35 for proper 36 month window
#
# Revision 1.57  2008/01/22 02:58:56  brian
# - Backtest fn now tested and working with new output of BruteForcePortfolios->BacktestData
#
# Revision 1.56  2008/01/22 02:10:20  brian
# -working much better, Backtest fn still fails with a subscriupt out of bounds error on some data
#
# Revision 1.55  2008/01/21 23:40:42  brian
# - adjust the way we reference list elements to do it numberically.  apparently it's not easy to reference by a string
#
# Revision 1.54  2008/01/21 17:50:24  brian
# - partial fix, Backtest fn still not working around lines 515-518
#
# Revision 1.53  2008/01/21 17:24:09  brian
# - adjust use of rownames for insample/outofsample in Backtest fn
#
# Revision 1.52  2008/01/21 17:18:38  brian
# - fix typo in matrix assignment
#
# Revision 1.51  2008/01/21 17:16:12  brian
# - add matrix for reult to Backtest fn
# - change max and min tests in Backtest fn to insert rowname of weighting vector rather than array index
#
# Revision 1.50  2008/01/21 16:31:36  brian
# - revise Backtest function to have utility functions for maximizing and minimizing lists
# - still need to initialize the result matrix
#
# Revision 1.49  2008/01/21 13:52:46  brian
# - fix typo in ThreeYrStdDev method in WeightedPortfolioUtility
#
# Revision 1.48  2008/01/21 13:49:09  brian
# - fix typo in ThreeYrGVaR method in WeightedPortfolioUtility
# - add comments on the subsetting method we had to use to make this work on large weightgrid
#
# Revision 1.47  2008/01/21 04:41:47  brian
# - fix naming and assignment of results in subsets
#
# Revision 1.46  2008/01/21 03:58:58  brian
# - move weightgridsave out of the outer loopy
#
# Revision 1.45  2008/01/21 03:26:32  brian
# - add drop=FALSE to subsetting of weightgrid to preserve rownames
#
# Revision 1.44  2008/01/21 03:02:19  brian
# - add ugly outer loop hack so this will work
#
# Revision 1.43  2008/01/21 01:39:15  brian
# - add switch and print statements for debug
#
# Revision 1.42  2008/01/20 23:07:58  brian
# - use matrix for results to avoid data.frame factor BS
#
# Revision 1.41  2008/01/20 21:13:59  brian
# - set colnames on result var when we create the object
#
# Revision 1.40  2008/01/20 21:05:45  brian
# - change to create structure with correct number of rows and columns on first pass
# - avoids warnings  about replacing 0-element row with x-element row
#
# Revision 1.39  2008/01/20 19:55:33  brian
# - create empty result var dataframe with right names for resultrows
# - assign resultrow by index to avoid memcopy problem
#
# Revision 1.38  2008/01/20 17:22:15  brian
# - fix row.names in initialization of resultrow data.frame
#
# Revision 1.37  2008/01/20 17:08:24  kris
# Compute SR more efficiently
#
# Revision 1.36  2008/01/20 16:30:50  brian
# - move multivariate moment calculations outside the row loop
#
# Revision 1.35  2008/01/20 16:26:21  brian
# - add M3 and M4 moments to parameters for all modSR function calls
#
# Revision 1.34  2008/01/20 16:14:53  brian
# - initialize result outside the loop in WeightedPortfolioUtility
# - initialize resultrow to have one row
#
# Revision 1.33  2008/01/20 14:54:55  brian
# - quote methods
#
# Revision 1.32  2008/01/20 14:53:05  brian
# - fix syntax errors and handling of inception, threeyr, form, to
#
# Revision 1.31  2008/01/20 13:55:44  brian
# - fix syntax error in switch on InceptionStdDev (missing comma)
#
# Revision 1.30  2008/01/20 13:49:39  brian
# - add Kris to copyright line
#
# Revision 1.29  2008/01/20 13:48:37  brian
# - fix syntax error
# - update methods to reflect changes to multivariate moments
#
# Revision 1.28  2008/01/20 13:35:34  brian
# - add missing brace in switch statement
#
# Revision 1.27  2008/01/20 12:07:24  kris
# - Changed function definitions in optim_functions.R and updated the function calls in optimizer.R to these functions
#
# Revision 1.26  2008/01/20 06:23:12  brian
# - convert GVaR functions
#
# Revision 1.25  2008/01/20 05:02:17  brian
# - add in centered moments and standard variables for period, inception, and 3yr series
#
# Revision 1.24  2008/01/19 16:48:01  brian
# - fix column name issues
# - add period, inception, and 3yr for each method
#
# Revision 1.23  2008/01/05 04:49:25  brian
# - add 'methods' argument to parameterize WeightedPortfolioUtility and BrutForcePortfolios functions
# - not yet tested, may have issues with column names
#
# Revision 1.22  2008/01/04 14:27:07  brian
# - convert to use functions from package PerformanceAnalytics
#
# Revision 1.21  2007/01/31 18:23:16  brian
# - cascade function name standardization from performance-analytics.R
#
# Revision 1.20  2007/01/30 15:54:57  brian
# - cascade function name standardization from extra_moments.R
#
# Revision 1.19  2007/01/26 13:24:02  brian
# - fix typo
#
# Revision 1.18  2006/12/03 17:42:02  brian
# - adjust utility functions in Backtest() to match 3yr statistices from BruteForcePortfolios
# - add more descriptive comments to BacktestDisplay()
# - add BacktestWeightDisplay() fn, not yet complete
# Bug 840
#
# Revision 1.17  2006/12/02 12:54:53  brian
# - modify BacktestData() fn to take a 'yeargrid' that matches
#    yeargrid from BruteForcePortfolios and loads those portfolios
# Bug 840
#
# Revision 1.16  2006/11/30 00:24:11  brian
# - remove 'inception' statistics from BruteForcePortfolios and Backtest fns
# - fix error in 'show' parameter of BacktestDisplay fn
# Bug 840
#
# Revision 1.15  2006/11/28 02:52:03  brian
# - add 3yr SharpeRatio.modified and 3yr modVaR
# - add fOptions require for Omega
# Bug 840
#
# Revision 1.14  2006/10/12 17:42:48  brian
# - put back omega utility fn
#
# Revision 1.13  2006/09/26 23:42:53  brian
# - add Equalweighted as column in Backtest vector fns
# - clean up NA handling in utility functions
# - add more error handling
#
# Revision 1.12  2006/09/26 21:53:41  brian
# - more fixes for NA's in data
#
# Revision 1.11  2006/09/26 12:07:04  brian
#  - add more NA handlinf and data series size checks
#  - comment out Omega for speed for now
#
# Revision 1.10  2006/09/22 15:30:44  brian
# - add separate vector to BacktestDisplay fn for benchmark returns
#
# Revision 1.9  2006/09/22 12:45:45  brian
# - add separate vector for benckmarkreturns to Backtest fn
# - better describe inputs to Backtest fn in comments
#
# Revision 1.8  2006/09/21 13:43:39  brian
# - add start timestamp for Backtest function
#
# Revision 1.7  2006/09/12 14:37:43  brian
# - add CVS tags
# - add CVS log
# - add confidentiality notice to top of file
#
# Revision 1.6 2006-09-12 09:31:37 brian
# - snapshot 2006-09-05 15:36
# - add functions and tweak existing to better handle larger data sets, cutting data
#
# Revision 1.5 2006-09-12 09:29:12 brian
# - snapshot 2006-08-30 19:03
# - add functions for conthly compounding returns
#
# Revision 1.4 2006-09-12 09:28:01 brian
# - snapshot 2006-08-29 23:01
# - add equal weighted utility functions
#
# Revision 1.3 2006-09-12 09:27:00 brian
# - snapshot 2006-08-29 21:58
# - Add functions to actually perform the backtest
#   using the results of the brute force statistics
#   generated on all possible portfolios.
#
# Revision 1.2 2006-09-12 09:25:06 brian
# - snapshot 2006-08-29
# - add BruteForcePortfolios, WeightedPortfolioUtility, and other small utility functions
#
# Revision 1.1 2006-09-12 09:23:14 brian
# - initial revision 2006-08-28
# Bug 840
###############################################################################
braverock/PortfolioAnalytics documentation built on April 18, 2024, 4:09 a.m.