From noreply at r-forge.r-project.org Thu Apr 3 19:34:35 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 3 Apr 2014 19:34:35 +0200 (CEST) Subject: [Blotter-commits] r1597 - pkg/blotter/R Message-ID: <20140403173436.05CFA186FBE@r-forge.r-project.org> Author: bodanker Date: 2014-04-03 19:34:35 +0200 (Thu, 03 Apr 2014) New Revision: 1597 Modified: pkg/blotter/R/perTradeStats.R Log: - slightly faster perTradeStats (at Samo Pahor's request) Modified: pkg/blotter/R/perTradeStats.R =================================================================== --- pkg/blotter/R/perTradeStats.R 2014-03-30 17:21:55 UTC (rev 1596) +++ pkg/blotter/R/perTradeStats.R 2014-04-03 17:34:35 UTC (rev 1597) @@ -92,49 +92,68 @@ else trades$Start <- head(trades$Start, -1) } + + # pre-allocate trades list + N <- length(trades$End) + trades <- c(trades, list( + Init.Pos = numeric(N), + Max.Pos = numeric(N), + Num.Txns = integer(N), + Max.Notional.Cost = numeric(N), + Net.Trading.PL = numeric(N), + MAE = numeric(N), + MFE = numeric(N), + Pct.Net.Trading.PL = numeric(N), + Pct.MAE = numeric(N), + Pct.MFE = numeric(N), + tick.Net.Trading.PL = numeric(N), + tick.MAE = numeric(N), + tick.MFE = numeric(N))) # calculate information about each trade - for(i in 1:length(trades$End)) + for(i in 1:N) { timespan <- seq.int(trades$Start[i], trades$End[i]) trade <- posPL[timespan] + n <- nrow(trade) - # add cost basis column - trade$Pos.Cost.Basis <- cumsum(trade$Txn.Value) - #add running posPL column - trade$PosPL <- trade$Pos.Value-trade$Pos.Cost.Basis - - #position sizes - trades$Init.Pos[i] <- first(trade$Pos.Qty) - trades$Max.Pos[i] <- first(trade[which(abs(trade$Pos.Qty)==max(abs(trade$Pos.Qty))),]$Pos.Qty) + # calculate cost basis, PosPL, Pct.PL, tick.PL columns + Pos.Qty <- trade[,"Pos.Qty"] # avoid repeated subsetting + Pos.Cost.Basis <- cumsum(trade[,"Txn.Value"]) + Pos.PL <- trade[,"Pos.Value"]-Pos.Cost.Basis + Pct.PL <- Pos.PL/abs(Pos.Cost.Basis) # broken for last timestamp (fixed below) + Tick.PL <- Pos.PL/abs(Pos.Qty)/tick_value # broken for last timestamp (fixed below) + Max.Pos.Qty.loc <- which.max(Pos.Qty) # find max position quantity location - #count number of transactions - trades$Num.Txns[i]<-length(which(trade$Txn.Value!=0)) + # position sizes + trades$Init.Pos[i] <- Pos.Qty[1] + trades$Max.Pos[i] <- Pos.Qty[Max.Pos.Qty.loc] + + # count number of transactions + trades$Num.Txns[i] <- sum(trade[,"Txn.Value"]!=0) # investment - trades$Max.Notional.Cost[i] <- first(trade[which(abs(trade$Pos.Qty)==max(abs(trade$Pos.Qty))),]$Pos.Cost.Basis) + trades$Max.Notional.Cost[i] <- Pos.Cost.Basis[Max.Pos.Qty.loc] # cash P&L - trades$Net.Trading.PL[i] <- last(trade)$PosPL - trades$MAE[i] <- min(0,trade$PosPL) - trades$MFE[i] <- max(0,trade$PosPL) + trades$Net.Trading.PL[i] <- Pos.PL[n] + trades$MAE[i] <- min(0,Pos.PL) + trades$MFE[i] <- max(0,Pos.PL) # percentage P&L - trade$Pct.PL <- trade$PosPL/abs(trade$Pos.Cost.Basis) #broken for last timestamp - trade$Pct.PL[length(trade$Pct.PL)]<-last(trade)$PosPL/abs(trades$Max.Notional.Cost[i]) + Pct.PL[n] <- Pos.PL[n]/abs(trades$Max.Notional.Cost[i]) - trades$Pct.Net.Trading.PL[i] <- last(trade$Pct.PL) - trades$Pct.MAE[i] <- min(0,trade$Pct.PL) - trades$Pct.MFE[i] <- max(0,trade$Pct.PL) + trades$Pct.Net.Trading.PL[i] <- Pct.PL[n] + trades$Pct.MAE[i] <- min(0,Pct.PL) + trades$Pct.MFE[i] <- max(0,Pct.PL) # tick P&L - #Net.Trading.PL/position/tick value=ticks - trade$tick.PL <- trade$PosPL/abs(trade$Pos.Qty)/tick_value #broken for last observation - trade$tick.PL[length(trade$tick.PL)] <- last(trade$PosPL)/abs(trades$Max.Pos[i])/tick_value + # Net.Trading.PL/position/tick value = ticks + Tick.PL[n] <- Pos.PL[n]/abs(trades$Max.Pos[i])/tick_value - trades$tick.Net.Trading.PL[i] <- last(trade$tick.PL) - trades$tick.MAE[i] <- min(0,trade$tick.PL) - trades$tick.MFE[i] <- max(0,trade$tick.PL) + trades$tick.Net.Trading.PL[i] <- Tick.PL[n] + trades$tick.MAE[i] <- min(0,Tick.PL) + trades$tick.MFE[i] <- max(0,Tick.PL) } trades$Start <- index(posPL)[trades$Start] trades$End <- index(posPL)[trades$End] From noreply at r-forge.r-project.org Fri Apr 4 01:27:10 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 4 Apr 2014 01:27:10 +0200 (CEST) Subject: [Blotter-commits] r1598 - in pkg/quantstrat: R man Message-ID: <20140403232710.883AE186F72@r-forge.r-project.org> Author: braverock Date: 2014-04-04 01:27:09 +0200 (Fri, 04 Apr 2014) New Revision: 1598 Modified: pkg/quantstrat/R/rebalance.rules.R pkg/quantstrat/man/addOrder.Rd pkg/quantstrat/man/rulePctEquity.Rd pkg/quantstrat/man/ruleSignal.Rd Log: - update docs Modified: pkg/quantstrat/R/rebalance.rules.R =================================================================== --- pkg/quantstrat/R/rebalance.rules.R 2014-04-03 17:34:35 UTC (rev 1597) +++ pkg/quantstrat/R/rebalance.rules.R 2014-04-03 23:27:09 UTC (rev 1598) @@ -30,7 +30,7 @@ #' add.rule(strategy.name, 'rulePctEquity', #' arguments=list(rebalance_on='months', #' trade.percent=.02, -#' refprice=quote(last(getPrice(mktdata)[paste('::',timestamp,sep='')])[,1]), +#' refprice=quote(last(getPrice(mktdata)[paste('::',curIndex,sep='')])[,1]), #' digits=0 #' ), #' type='rebalance', Modified: pkg/quantstrat/man/addOrder.Rd =================================================================== --- pkg/quantstrat/man/addOrder.Rd 2014-04-03 17:34:35 UTC (rev 1597) +++ pkg/quantstrat/man/addOrder.Rd 2014-04-03 23:27:09 UTC (rev 1598) @@ -4,7 +4,7 @@ \usage{ addOrder(portfolio, symbol, timestamp, qty, price, ordertype, side, threshold = NULL, orderset = "", status = "open", - statustimestamp = "", prefer = NULL, delay = 1e-05, tmult = FALSE, + statustimestamp = "", prefer = NULL, delay = 0.00001, tmult = FALSE, replace = TRUE, return = FALSE, ..., TxnFees = 0, label = "", time.in.force = "") } Modified: pkg/quantstrat/man/rulePctEquity.Rd =================================================================== --- pkg/quantstrat/man/rulePctEquity.Rd 2014-04-03 17:34:35 UTC (rev 1597) +++ pkg/quantstrat/man/rulePctEquity.Rd 2014-04-03 23:27:09 UTC (rev 1598) @@ -50,7 +50,7 @@ add.rule(strategy.name, 'rulePctEquity', arguments=list(rebalance_on='months', trade.percent=.02, - refprice=quote(last(getPrice(mktdata)[paste('::',timestamp,sep='')])[,1]), + refprice=quote(last(getPrice(mktdata)[paste('::',curIndex,sep='')])[,1]), digits=0 ), type='rebalance', Modified: pkg/quantstrat/man/ruleSignal.Rd =================================================================== --- pkg/quantstrat/man/ruleSignal.Rd 2014-04-03 17:34:35 UTC (rev 1597) +++ pkg/quantstrat/man/ruleSignal.Rd 2014-04-03 23:27:09 UTC (rev 1598) @@ -4,7 +4,7 @@ \usage{ ruleSignal(mktdata = mktdata, timestamp, sigcol, sigval, orderqty = 0, ordertype, orderside = NULL, orderset = NULL, threshold = NULL, - tmult = FALSE, replace = TRUE, delay = 1e-04, osFUN = "osNoOp", + tmult = FALSE, replace = TRUE, delay = 0.0001, osFUN = "osNoOp", pricemethod = c("market", "opside", "active"), portfolio, symbol, ..., ruletype, TxnFees = 0, prefer = NULL, sethold = FALSE, label = "", order.price = NULL, chain.price = NULL, time.in.force = "") From noreply at r-forge.r-project.org Wed Apr 16 18:09:40 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 16 Apr 2014 18:09:40 +0200 (CEST) Subject: [Blotter-commits] r1599 - in pkg/blotter: R man Message-ID: <20140416160940.5936D180384@r-forge.r-project.org> Author: braverock Date: 2014-04-16 18:09:40 +0200 (Wed, 16 Apr 2014) New Revision: 1599 Modified: pkg/blotter/R/tradeStats.R pkg/blotter/man/tradeStats.Rd Log: - add option inclZeroDays to tradeStats Modified: pkg/blotter/R/tradeStats.R =================================================================== --- pkg/blotter/R/tradeStats.R 2014-04-03 23:27:09 UTC (rev 1598) +++ pkg/blotter/R/tradeStats.R 2014-04-16 16:09:40 UTC (rev 1599) @@ -17,6 +17,14 @@ #' something like \code{textplot} or \code{\link{data.frame}}, with rounding, #' fancy formatting, etc. as your needs dictate. #' +#' Option \code{inclZeroDays}, if \code{TRUE}, will include all transaction P&L, +#' including for days in which the strategy was not in the market, +#' for daily statistics. +#' This can prevent irrationally good looking daily statistics for strategies +#' which spend a fair amount of time out of the market. For strategies which +#' are always in the market, the statistics should be (nearly) the same. +#' Default is \code{FALSE} for backwards compatibility. +#' #' If you have additional trade statistics you want added here, please share. #' We find it unlikely that any transaction-level statistics that can be #' calculated independently of strategy rules could be considered proprietary. @@ -37,6 +45,7 @@ #' @param Symbols character vector of symbol strings, default NULL #' @param use for determines whether numbers are calculated from transactions or round-trip trades (for tradeStats) or equity curve (for dailyStats) #' @param tradeDef string to determine which definition of 'trade' to use. Currently "flat.to.flat" (the default) and "flat.to.reduced" are implemented. +#' @param inclZeroDays TRUE/FALSE, whether to include zero P&L days in daily calcs, default FALSE for backwards compatibility. #' @author Lance Levenson, Brian Peterson #' @export #' @importFrom zoo as.Date @@ -88,7 +97,7 @@ #' Buy and hold return #' #' Josh has suggested adding \%-return based stats too -tradeStats <- function(Portfolios, Symbols ,use=c('txns','trades'), tradeDef='flat.to.flat') +tradeStats <- function(Portfolios, Symbols ,use=c('txns','trades'), tradeDef='flat.to.flat',inclZeroDays=FALSE) { ret <- NULL use <- use[1] #use the first(default) value only if user hasn't specified @@ -116,7 +125,9 @@ next } - DailyPL <- apply.daily(PL.ne0,sum) + if(!isTRUE(inclZeroDays)) DailyPL <- apply.daily(PL.ne0,sum) + else DailyPL <- apply.daily(txn$Net.Txn.Realized.PL,sum) + AvgDailyPL <- mean(DailyPL) MedDailyPL <- median(DailyPL) StdDailyPL <- sd(as.numeric(as.vector(DailyPL))) Modified: pkg/blotter/man/tradeStats.Rd =================================================================== --- pkg/blotter/man/tradeStats.Rd 2014-04-03 23:27:09 UTC (rev 1598) +++ pkg/blotter/man/tradeStats.Rd 2014-04-16 16:09:40 UTC (rev 1599) @@ -4,7 +4,7 @@ \title{calculate statistics on transactions and P&L for a symbol or symbols in a portfolio or portfolios} \usage{ tradeStats(Portfolios, Symbols, use = c("txns", "trades"), - tradeDef = "flat.to.flat") + tradeDef = "flat.to.flat", inclZeroDays = FALSE) dailyStats(Portfolios, use = c("equity", "txns")) } @@ -21,6 +21,10 @@ \item{tradeDef}{string to determine which definition of 'trade' to use. Currently "flat.to.flat" (the default) and "flat.to.reduced" are implemented.} + + \item{inclZeroDays}{TRUE/FALSE, whether to include zero + P&L days in daily calcs, default FALSE for backwards + compatibility.} } \value{ a \code{data.frame} containing: @@ -48,7 +52,7 @@ \code{\link{dailyStats}} for all days } \item{Med.Daily.PL}{ median daily P&L } \item{Std.Dev.Daily.PL}{ standard deviation of daily P&L } -\item{Ann.Sharpe}{annualized Sharpe-like ratio, assuming no +\item(Ann.Sharpe){annualized Sharpe-like ratio, assuming no outside capital additions and 252 day count convention} \item{Max.Drawdown}{ max drawdown } \item{Avg.WinLoss.Ratio}{ ratio of mean winning over mean @@ -80,6 +84,15 @@ \code{\link{data.frame}}, with rounding, fancy formatting, etc. as your needs dictate. +Option \code{inclZeroDays}, if \code{TRUE}, will include +all transaction P&L, including for days in which the +strategy was not in the market, for daily statistics. This +can prevent irrationally good looking daily statistics for +strategies which spend a fair amount of time out of the +market. For strategies which are always in the market, the +statistics should be (nearly) the same. Default is +\code{FALSE} for backwards compatibility. + If you have additional trade statistics you want added here, please share. We find it unlikely that any transaction-level statistics that can be calculated From noreply at r-forge.r-project.org Wed Apr 16 23:16:27 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 16 Apr 2014 23:16:27 +0200 (CEST) Subject: [Blotter-commits] r1600 - pkg/blotter/R Message-ID: <20140416211627.A82381867C0@r-forge.r-project.org> Author: efmrforge Date: 2014-04-16 23:16:27 +0200 (Wed, 16 Apr 2014) New Revision: 1600 Modified: pkg/blotter/R/addTxn.R Log: Added checking for TxnQty and TxnPrice column names Modified: pkg/blotter/R/addTxn.R =================================================================== --- pkg/blotter/R/addTxn.R 2014-04-16 16:09:40 UTC (rev 1599) +++ pkg/blotter/R/addTxn.R 2014-04-16 21:16:27 UTC (rev 1600) @@ -173,9 +173,19 @@ # initialize new transaction object NewTxns <- xts(matrix(NA_real_, nrow(TxnData), 10L), index(TxnData)) colnames(NewTxns) <- c('Txn.Qty', 'Txn.Price', 'Txn.Value', 'Txn.Avg.Cost', 'Pos.Qty', 'Pos.Avg.Cost', 'Gross.Txn.Realized.PL', 'Txn.Fees', 'Net.Txn.Realized.PL', 'Con.Mult') - - NewTxns$Txn.Qty <- as.numeric(TxnData$TxnQty) - NewTxns$Txn.Price <- as.numeric(TxnData$TxnPrice) +1 + if(!("TxnQty" %in% colnames(TxnData))) { + warning(paste("No TxnQty column found, what did you call it?")) + } else { + NewTxns$Txn.Qty <- as.numeric(TxnData$TxnQty) + } + if(!("TxnPrice" %in% colnames(TxnData))) { + warning(paste("No TxnPrice column found, what did you call it?")) + } else { + NewTxns$Txn.Qty <- as.numeric(TxnData$TxnPrice) + } + #NewTxns$Txn.Qty <- as.numeric(TxnData$TxnQty) + #NewTxns$Txn.Price <- as.numeric(TxnData$TxnPrice) if("TxnFees" %in% colnames(TxnData)) { NewTxns$Txn.Fees <- as.numeric(TxnData$TxnFees) } else { @@ -303,7 +313,7 @@ ############################################################################### # Blotter: Tools for transaction-oriented trading systems development # for R (see http://r-project.org/) -# Copyright (c) 2008-2014 Peter Carl and Brian G. Peterson +# Copyright (c) 2008-2011 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 From noreply at r-forge.r-project.org Wed Apr 16 23:19:46 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 16 Apr 2014 23:19:46 +0200 (CEST) Subject: [Blotter-commits] r1601 - pkg/blotter/R Message-ID: <20140416211946.6C040186A67@r-forge.r-project.org> Author: efmrforge Date: 2014-04-16 23:19:45 +0200 (Wed, 16 Apr 2014) New Revision: 1601 Modified: pkg/blotter/R/addTxn.R Log: Fixed copyright Modified: pkg/blotter/R/addTxn.R =================================================================== --- pkg/blotter/R/addTxn.R 2014-04-16 21:16:27 UTC (rev 1600) +++ pkg/blotter/R/addTxn.R 2014-04-16 21:19:45 UTC (rev 1601) @@ -313,7 +313,7 @@ ############################################################################### # Blotter: Tools for transaction-oriented trading systems development # for R (see http://r-project.org/) -# Copyright (c) 2008-2011 Peter Carl and Brian G. Peterson +# Copyright (c) 2008-2014 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 From noreply at r-forge.r-project.org Thu Apr 17 22:08:39 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 17 Apr 2014 22:08:39 +0200 (CEST) Subject: [Blotter-commits] r1602 - pkg/quantstrat/demo Message-ID: <20140417200840.1DE76187600@r-forge.r-project.org> Author: efmrforge Date: 2014-04-17 22:08:38 +0200 (Thu, 17 Apr 2014) New Revision: 1602 Modified: pkg/quantstrat/demo/luxor.1.strategy.basic.R Log: Removed redundant requires(quantstrat) Modified: pkg/quantstrat/demo/luxor.1.strategy.basic.R =================================================================== --- pkg/quantstrat/demo/luxor.1.strategy.basic.R 2014-04-16 21:19:45 UTC (rev 1601) +++ pkg/quantstrat/demo/luxor.1.strategy.basic.R 2014-04-17 20:08:38 UTC (rev 1602) @@ -10,8 +10,6 @@ require(quantstrat) -require(quantstrat) - ##### PLACE DEMO AND TEST DATES HERE ################# # #if(isTRUE(options('in_test')$in_test)) From noreply at r-forge.r-project.org Mon Apr 21 00:07:47 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 21 Apr 2014 00:07:47 +0200 (CEST) Subject: [Blotter-commits] r1603 - pkg/quantstrat/R Message-ID: <20140420220754.53063187681@r-forge.r-project.org> Author: ilya_kipnis Date: 2014-04-21 00:07:43 +0200 (Mon, 21 Apr 2014) New Revision: 1603 Modified: pkg/quantstrat/R/paramsets.R Log: Removing verbose arg from line 503 of paramsets.R Modified: pkg/quantstrat/R/paramsets.R =================================================================== --- pkg/quantstrat/R/paramsets.R 2014-04-17 20:08:38 UTC (rev 1602) +++ pkg/quantstrat/R/paramsets.R 2014-04-20 22:07:43 UTC (rev 1603) @@ -500,7 +500,7 @@ } strategy <- install.param.combo(strategy, param.combo, paramset.label) - applyStrategy(strategy, portfolios=result$portfolio.st, mktdata=mktdata, verbose=verbose, ...) + applyStrategy(strategy, portfolios=result$portfolio.st, mktdata=mktdata, ...) if(exists('redisContext')) { From noreply at r-forge.r-project.org Fri Apr 25 14:57:49 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 25 Apr 2014 14:57:49 +0200 (CEST) Subject: [Blotter-commits] r1604 - pkg/quantstrat/R Message-ID: <20140425125749.ACE1A187327@r-forge.r-project.org> Author: braverock Date: 2014-04-25 14:57:49 +0200 (Fri, 25 Apr 2014) New Revision: 1604 Modified: pkg/quantstrat/R/orders.R Log: - add is.null check in TxnFees Modified: pkg/quantstrat/R/orders.R =================================================================== --- pkg/quantstrat/R/orders.R 2014-04-20 22:07:43 UTC (rev 1603) +++ pkg/quantstrat/R/orders.R 2014-04-25 12:57:49 UTC (rev 1604) @@ -285,6 +285,7 @@ if(is.na(qty)) stop("qty",qty,"must not be NA") if(!is.numeric(price)) stop (paste("Price must be numeric:",price)) if(is.null(price)) stop("price ",price," must not be NULL") + if(is.null(TxnFees)) stop("TxnFees ",TxnFees," must not be NULL") if(is.na(price)) stop("order at timestamp ", timestamp, " must not have price of NA") #spreads can have a zero price #if(price==0) warning(paste(ordertype, "order for", qty, "has a price of zero.")) From noreply at r-forge.r-project.org Sun Apr 27 07:27:17 2014 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 27 Apr 2014 07:27:17 +0200 (CEST) Subject: [Blotter-commits] r1605 - pkg/blotter/R Message-ID: <20140427052717.BBC87186D62@r-forge.r-project.org> Author: bodanker Date: 2014-04-27 07:26:52 +0200 (Sun, 27 Apr 2014) New Revision: 1605 Modified: pkg/blotter/R/addTxn.R Log: - Fixes to addTxns Modified: pkg/blotter/R/addTxn.R =================================================================== --- pkg/blotter/R/addTxn.R 2014-04-25 12:57:49 UTC (rev 1604) +++ pkg/blotter/R/addTxn.R 2014-04-27 05:26:52 UTC (rev 1605) @@ -173,7 +173,7 @@ # initialize new transaction object NewTxns <- xts(matrix(NA_real_, nrow(TxnData), 10L), index(TxnData)) colnames(NewTxns) <- c('Txn.Qty', 'Txn.Price', 'Txn.Value', 'Txn.Avg.Cost', 'Pos.Qty', 'Pos.Avg.Cost', 'Gross.Txn.Realized.PL', 'Txn.Fees', 'Net.Txn.Realized.PL', 'Con.Mult') -1 + if(!("TxnQty" %in% colnames(TxnData))) { warning(paste("No TxnQty column found, what did you call it?")) } else { @@ -182,10 +182,8 @@ if(!("TxnPrice" %in% colnames(TxnData))) { warning(paste("No TxnPrice column found, what did you call it?")) } else { - NewTxns$Txn.Qty <- as.numeric(TxnData$TxnPrice) + NewTxns$Txn.Price <- as.numeric(TxnData$TxnPrice) } - #NewTxns$Txn.Qty <- as.numeric(TxnData$TxnQty) - #NewTxns$Txn.Price <- as.numeric(TxnData$TxnPrice) if("TxnFees" %in% colnames(TxnData)) { NewTxns$Txn.Fees <- as.numeric(TxnData$TxnFees) } else {