Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ export(initSymbol)
export(is.strategy)
export(load.strategy)
export(match.names)
export(osFixedPercent)
export(osMaxPos)
export(osNoOp)
export(post.signal.returns)
Expand Down
43 changes: 43 additions & 0 deletions R/osFUNs.R
Original file line number Diff line number Diff line change
Expand Up @@ -231,6 +231,49 @@ osMaxPos <- function(data, timestamp, orderqty, ordertype, orderside, portfolio,
return(0)
}

#' Order sizing function for fixing the position limit in percentage
#'
#' Allows to fix the position limit in percentage of the current portfolio equity.
#'
#' Slows down the backtesting process as it updates the portfolio at each timestamp and not at the end of the timeseries.
#'
#' @param data an xts object containing market data. depending on rules, may need to be in OHLCV or BBO formats, and may include indicator and signal information
#' @param timestamp timestamp coercible to POSIXct that will be the time the order will be inserted on
#' @param orderqty numeric quantity of the desired order, modified by osFUN
#' @param portfolio text name of the portfolio to get the equity
#' @param tradesize position limit in percentage, e.g. 0.3 for 30\%
#' @param leverage the leverage size, relevant for margin trading and derivatives market
#' @param verbose set it to true if you want to print logs on the console
#' @param ... any other passthru parameters
#' @seealso \code{\link{addPosLimit}}, \code{\link{getPosLimit}}, \code{\link{osMaxPos}}
#' @export
#' @author Valery Barmin \href{https://github.com/randomsuffer}{@randomsuffer}
osFixedPercent <- function(data, timestamp, orderqty, portfolio, tradesize, leverage=1, verbose=false, ...) {
if(!exists("tradesize")) stop("No trade size defined")

# update the portfolio
updatePortf(portfolio)
portfolio <- getPortfolio(portfolio)

# calculate current equity
equity <- initEq + sum(portfolio$summary$Period.Realized.PL)

# calculate maximum position size, an initial margin and order quantity
lastclose <- as.numeric(Cl(data[timestamp,]))
maxdollarpos <- equity * tradesize
initialmargin <- lastclose / leverage
orderqty <- sign(orderqty) * floor(maxdollarpos / initialmargin)

if (verbose) print(paste('osFixedPercent:',
'lastclose =', lastclose,
'equity =', equity,
'maxdollarpos =', maxdollarpos,
'initialmargin =', initialmargin,
'orderqty =', orderqty))

return(orderqty)
}

#TODO ruleRiskPosLimits to check for overfilled position and scale back

###############################################################################
Expand Down
38 changes: 38 additions & 0 deletions man/osFixedPercent.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

40 changes: 40 additions & 0 deletions tests/testthat/test_osFixedPercent.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
stopifnot(require(testthat))
stopifnot(require(quantstrat))
context("osFixedPercent")

Sys.setenv(TZ = 'UTC')

symbol <- "sample_matrix"
portfolio <- "test_osFixedPercent"

defaultcurrency <- 'USD'
currency(defaultcurrency)
stock(symbol, currency = defaultcurrency, multiplier = 1)

initEq <- 1000

rm.strat(portfolio)
initPortf(portfolio, symbol)
addPosLimit(portfolio, symbol, "2007-05-30", initEq)

data(sample_matrix)
sample_matrix <- xts(sample_matrix, order.by = as.POSIXct(strptime(row.names(sample_matrix), "%Y-%m-%d")))
assign(symbol, sample_matrix)

###############################################################################

orderqty <- 1
tradesize <- 0.3
leverage <- 5

# test_that("test 1", {
# timestamp <- as.Date("2007-05-30")
# qty <- osFixedPercent(sample_matrix, timestamp, orderqty, portfolio, initEq, tradesize, leverage)
# expect_equal(qty * as.numeric(Cl(sample_matrix[timestamp, ])) / leverage < initEq * tradesize, T)
# })
#
# test_that("test 2", {
# timestamp <- as.Date("2007-05-08")
# qty <- osFixedPercent(sample_matrix, timestamp, orderqty, portfolio, initEq, tradesize, leverage)
# expect_equal(qty * as.numeric(Cl(sample_matrix[timestamp, ])) / leverage < initEq * tradesize, T)
# })