[R-SIG-Finance] fPortfolio - Maximum Return Portfolio
Diethelm Wuertz
wuertz at itp.phys.ethz.ch
Thu May 28 00:20:37 CEST 2009
Yaakov Moser wrote:
This works
maxriskPortfolio <-
function (data, spec = portfolioSpec(), constraints = "LongOnly")
{
Data = portfolioData(data, spec)
data <- getSeries(Data)
targetRiskFun <- function(x, data, spec, constraints) {
setTargetReturn(spec) = x[1]
Solver = match.fun(getSolver(spec))
ans = Solver(data, spec, constraints)
# DW:
# Take care that the status ans$status is always 0
# If the solver fails set the value of the risk to the global
# min risk portfolio!
# Use the function try() that the calculation does not break!
targetRisk = -ans$objective
attr(targetRisk, "weights") <- ans$weights
attr(targetRisk, "status") <- ans$status
return(targetRisk)
}
# DW:
# Take care that the interval range may be large enough if short selling
# is allowed, that requires an adaption of the range!
# DW:
# Increase the tolerance to be sure that optimize has converged!
portfolio <- optimize(targetRiskFun, interval = range(getMu(Data)),
data = Data, spec = spec, constraints = constraints,
tol = .Machine$double.eps^0.5)
setWeights(spec) <- attr(portfolio$objective, "weights")
setStatus(spec) <- attr(portfolio$objective, "status")
portfolio = feasiblePortfolio(data, spec, constraints)
portfolio at call = match.call()
portfolio at title = "Maximum Risk Portfolio"
portfolio
}
maxriskPortfolio(SMALLCAP.RET[, 1:3])
-d
> I tried reversing the sign by redefining a maxriskPortfolio function
> based on the minriskPortfolio as you suggested.
>
> I changed the one line to be:
>
> targetRisk = -ans$objective
>
>
> The function ran - and found something close to the maxriskPortfolio,
> but it is not the end of the efficient frontier...
>
> My constraints were long-only, so it should have been 100% in one
> asset, but it turned out to be 99.54% only, with the rest elsewhere.
>
>
> Any suggestions?
>
>
> See sample program below.
>
>
> Thanks
>
>
> Yaakov
>
>
> library(fPortfolio)
> Data=SMALLCAP.RET
> Data=Data[,c(1:3)]
> Spec=portfolioSpec()
> constraints="long-only"
> maxriskPortfolio <- function (data, spec = portfolioSpec(),
> constraints = "LongOnly")
> {
> Data = portfolioData(data, spec)
> data <- getSeries(Data)
> targetRiskFun <- function(x, data, spec, constraints) {
> setTargetReturn(spec) = x[1]
> Solver = match.fun(getSolver(spec))
> ans = Solver(data, spec, constraints)
> targetRisk = -ans$objective
> attr(targetRisk, "weights") <- ans$weights
> attr(targetRisk, "status") <- ans$status
> return(targetRisk)
> }
> portfolio <- optimize(targetRiskFun, interval = range(getMu(Data)),
> data = Data, spec = spec, constraints = constraints)
> STATUS = attr(portfolio$objective, "status")
> if (STATUS != 0) {
> cat("\nExecution stopped:")
> cat("\n The minimum risk portfolio could not be computed.")
> cat("\nPossible Reason:")
> cat("\n Your portfolio constraints may be too restrictive.")
> cat("\nStatus Information:")
> cat("\n status=", STATUS, " from solver ", getSolver(spec),
> ".", sep = "")
> cat("\n")
> stop(call. = FALSE, show.error.messages = "\n returned from
> Rmetrics")
> }
> setWeights(spec) <- attr(portfolio$objective, "weights")
> setStatus(spec) <- attr(portfolio$objective, "status")
> portfolio = feasiblePortfolio(data, spec, constraints)
> portfolio at call = match.call()
> portfolio at title = "Maximum Risk Portfolio"
> portfolio
> }
> minriskPortfolio(Data,Spec,constraints)
> maxriskPortfolio(Data,Spec,constraints)
> portfolioFrontier(Data,Spec,constraints)
>
>
>
>
>
> -------- Original Message --------
> Subject: Re: [R-SIG-Finance] fPortfolio - Maximum Return Portfolio
> From: Diethelm Wuertz <wuertz at itp.phys.ethz.ch>
> To: Yaakov Moser <ymoser at gmail.com>
> CC: r-sig-finance at stat.math.ethz.ch
> Date: 27 May 2009 10:05:42
>
>> Yaakov Moser wrote:
>>
>> There may be a faster solution (compared to my previous email), just
>> look for the portfolio with the highest risk, i.e. the lowest
>> negative risk. That can be easily implemented
>> by reversion of the sign of the objective risk function in the
>> portfolio optimization.
>>> Can anyone suggest a simple way to find the maximum return portfolio
>>> on an efficient frontier with fPortfolio?
>>>
>>> Without constraints, this is simply the asset with the highest return.
>>> However, with constraints, it needs to be solved.
>>>
>>> The only option I have come up with so far is to use the
>>> portfolioFrontier function (ideally with a large number of points),
>>> and then take the end one.
>>> However, this point varies depending on how many points were
>>> selected in the Spec...
>>>
>>> As far as I can tell, there is no built in functionality equivalent
>>> to the minriskPortfolio.
>>>
>>> Thanks
>>>
>>> Yaakov
>>>
>>> _______________________________________________
>>> R-SIG-Finance at stat.math.ethz.ch mailing list
>>> https://stat.ethz.ch/mailman/listinfo/r-sig-finance
>>> -- Subscriber-posting only.
>>> -- If you want to post, subscribe first.
>>>
>>
>>
>
More information about the R-SIG-Finance
mailing list