Skip to content

Instantly share code, notes, and snippets.

@jaymon0703
Last active January 24, 2017 19:02
Show Gist options
  • Save jaymon0703/42eff377b2fe30049663ef74428bedbc to your computer and use it in GitHub Desktop.
Save jaymon0703/42eff377b2fe30049663ef74428bedbc to your computer and use it in GitHub Desktop.
perTradeStats with "increased.to.reduced" assuming FIFO to line up start and end dates for round turn trades
#' calculate flat to flat per-trade statistics
#'
#' One 'trade' is defined as the entire time the symbol is not flat.
#' It may contain many transactions. From the initial transaction that
#' moves the position away from zero to the last transaction that flattens the
#' position is all one 'trade' for the purposes of this function.
#'
#' This is sometimes referred to as 'flat to flat' analysis.
#'
#' Note that a trade that is open at the end of the measured period will
#' be marked to the timestamp of the end of the series.
#' If that trade is later closed, the stats for it will likely change.
#' This is 'mark to market' for the open position, and corresponds to
#' most trade accounting systems and risk systems in including the open
#' position in reporting.
#'
#' @param Portfolio string identifying the portfolio
#' @param Symbol string identifying the symbol to examin trades for. If missing, the first symbol found in the \code{Portfolio} portfolio will be used
#' @param includeOpenTrade whether to process only finished trades, or the last trade if it is still open, default TRUE
#' @param tradeDef string to determine which definition of 'trade' to use. Currently "flat.to.flat" (the default) and "flat.to.reduced" are implemented.
#' @param \dots any other passthrough parameters
#' @author Brian G. Peterson, Jan Humme
#' @references Tomasini, E. and Jaekle, U. \emph{Trading Systems - A new approach to system development and portfolio optimisation} (ISBN 978-1-905641-79-6)
#' @return
#' A \code{data.frame} containing:
#'
#' \describe{
#' \item{Start}{the \code{POSIXct} timestamp of the start of the trade}
#' \item{End}{the \code{POSIXct} timestamp of the end of the trade, when flat}
#' \item{Init.Pos}{the initial position on opening the trade}
#' \item{Max.Pos}{the maximum (largest) position held during the open trade}
#' \item{Num.Txns}{ the number of transactions included in this trade}
#' \item{Max.Notional.Cost}{ the largest notional investment cost of this trade}
#' \item{Net.Trading.PL}{ net trading P&L in the currency of \code{Symbol}}
#' \item{MAE}{ Maximum Adverse Excursion (MAE), in the currency of \code{Symbol}}
#' \item{MFE}{ Maximum Favorable Excursion (MFE), in the currency of \code{Symbol}}
#' \item{Pct.Net.Trading.PL}{ net trading P&L in percent of invested \code{Symbol} price gained or lost}
#' \item{Pct.MAE}{ Maximum Adverse Excursion (MAE), in percent}
#' \item{Pct.MFE}{ Maximum Favorable Excursion (MFE), in percent}
#' \item{tick.Net.Trading.PL}{ net trading P&L in ticks}
#' \item{tick.MAE}{ Maximum Adverse Excursion (MAE) in ticks}
#' \item{tick.MFE}{ Maximum Favorable Excursion (MFE) in ticks}
#' }
#' @seealso \code{\link{chart.ME}} for a chart of MAE and MFE derived from this function,
#' and \code{\link{tradeStats}} for a summary view of the performance
#' @export
perTradeStats <- function(Portfolio, Symbol, includeOpenTrade=TRUE, tradeDef="flat.to.flat", ...) {
portf <- .getPortfolio(Portfolio)
if(missing(Symbol)) Symbol <- ls(portf$symbols)[[1]]
posPL <- portf$symbols[[Symbol]]$posPL
instr <- getInstrument(Symbol)
tick_value <- instr$multiplier*instr$tick_size
tradeDef <- match.arg(tradeDef, c("flat.to.flat","flat.to.reduced","increased.to.reduced"))
trades <- list()
switch(tradeDef,
flat.to.flat = {
# identify start and end for each trade, where end means flat position
trades$Start <- which(posPL$Pos.Qty!=0 & lag(posPL$Pos.Qty)==0)
trades$End <- which(posPL$Pos.Qty==0 & lag(posPL$Pos.Qty)!=0)
},
flat.to.reduced = {
# find all transactions that bring position closer to zero ('trade ends')
decrPos <- diff(abs(posPL$Pos.Qty)) < 0
# find all transactions that open a position ('trade starts')
initPos <- posPL$Pos.Qty!=0 & lag(posPL$Pos.Qty)==0
# 'trades' start when we open a position, so determine which starts correspond to each end
# add small amount to Start index, so starts will always occur before ends in StartEnd
Start <- xts(initPos[initPos,which.i=TRUE],index(initPos[initPos])+1e-5)
End <- xts(decrPos[decrPos,which.i=TRUE],index(decrPos[decrPos]))
StartEnd <- merge(Start,End)
StartEnd$Start <- na.locf(StartEnd$Start)
StartEnd <- StartEnd[!is.na(StartEnd$End),]
# populate trades list
trades$Start <- drop(coredata(StartEnd$Start))
trades$End <- drop(coredata(StartEnd$End))
# add extra 'trade start' if there's an open trade, so 'includeOpenTrade' logic will work
if(last(posPL)[,"Pos.Qty"] != 0)
trades$Start <- c(trades$Start, last(trades$Start))
},
increased.to.reduced = {
# find all transactions that bring position closer to zero ('trade ends')
decrPos <- diff(abs(posPL$Pos.Qty)) < 0
decrPosCount <- ifelse(diff(abs(posPL$Pos.Qty)) < 0,-1,0)
decrPosCount <- ifelse(decrPosCount[-1] == 0, 0, cumsum(decrPosCount[-1]))
decrPosQty <- ifelse(diff(abs(posPL$Pos.Qty)) < 0, diff(abs(posPL$Pos.Qty)),0)
decrPosQtyCum <- ifelse(decrPosQty[-1] == 0, 0, cumsum(decrPosQty[-1])) #subset for the leading NA
# find all transactions that take position further from zero ('trade starts')
incrPos <- diff(abs(posPL$Pos.Qty)) > 0
incrPosCount <- ifelse(diff(abs(posPL$Pos.Qty)) > 0,1,0)
incrPosCount <- ifelse(incrPosCount[-1] == 0, 0, cumsum(incrPosCount[-1]))
incrPosQty <- ifelse(diff(abs(posPL$Pos.Qty)) > 0, diff(abs(posPL$Pos.Qty)),0)
incrPosQtyCum <- ifelse(incrPosQty[-1] == 0, 0, cumsum(incrPosQty[-1])) #subset for the leading NA
df <- cbind(incrPosCount, incrPosQty, incrPosQtyCum, decrPosCount, decrPosQty, decrPosQtyCum)[-1]
names(df) <- c("incrPosCount", "incrPosQty", "incrPosQtyCum", "decrPosCount", "decrPosQty", "decrPosQtyCum")
consol <- cbind(incrPosQtyCum,decrPosQtyCum)
names(consol)<-c('incrPosQtyCum','decrPosQtyCum')
consol$decrPosQtyCum<- -consol$decrPosQtyCum
consol$incrPosQtyCum[consol$incrPosQtyCum==0]<-NA
consol$decrPosQtyCum[consol$decrPosQtyCum==0]<-NA
idx <- findInterval(na.omit(consol$decrPosQtyCum),na.omit(consol$incrPosQtyCum))
#consol <- cbind(na.omit(consol$incrPosQtyCum), na.omit(consol$decrPosQtyCum), idx)
# populate trades list
idx <- idx[!is.na(idx)] # remove NAs from idx vector
idx <- idx[-length(idx)] # remove last element...see description ***TODO: add description with example dataset?
idx <- idx + 1 # +1 as findInterval() finds the lower bound of the range...see description ***TODO: add description with example dataset?
trades$Start[1] <- first(which(consol$incrPosQtyCum != "NA"))
trades$End <- which(consol$decrPosQtyCum != "NA")
trades$Start[2:length(trades$End)] <- which(consol$incrPosQtyCum != "NA")[idx]
# now add 1 to idx for missing initdate from incr/decrPosQtyCum - adds consistency with falt.to.reduced and flat.to.flat
trades$Start <- trades$Start + 1
trades$End <- trades$End + 1
# add extra 'trade start' if there's an open trade, so 'includeOpenTrade' logic will work
if(last(posPL)[,"Pos.Qty"] != 0)
trades$Start <- c(trades$Start, last(trades$Start))
}
)
# if the last trade is still open, adjust depending on whether wants open trades or not
if(length(trades$Start)>length(trades$End))
{
if(includeOpenTrade)
trades$End <- c(trades$End,nrow(posPL))
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:N)
{
timespan <- seq.int(trades$Start[i], trades$End[i])
trade <- posPL[timespan]
n <- nrow(trade)
# 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(abs(Pos.Qty)) # find max position quantity location
# 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] <- Pos.Cost.Basis[Max.Pos.Qty.loc]
# cash P&L
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
Pct.PL[n] <- Pos.PL[n]/abs(trades$Max.Notional.Cost[i])
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
Tick.PL[n] <- Pos.PL[n]/abs(trades$Max.Pos[i])/tick_value
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]
return(as.data.frame(trades))
} # end fn perTradeStats
################################################################################################################
# Test Datasets
############################################### Scenario 1
Date <- seq.int(1,10,1)
TxnQty <- c(100,50,50,-100,-50,50,-50,-50,+50,-50)
TxnPrice <- c(101,102,103,104,105,106,107,108,109,110) # just using silly prices
Cum <- c(100,150,200,100,50,100,50,0,50,0)
IncSeq <- c(1,2,3,0,0,4,0,0,5,0)
IncCum <- c(100,150,200,0,0,250,0,0,300,0)
DecSeq <- c(0,0,0,-1,-2,0,-3,-4,0,-5)
DecCum <- c(0,0,0,-100,-150,0,-200,-250,0,-300)
Start <- c(0,0,0,1,2,0,3,4,0,5)
df_test1 <- data.frame(cbind(Date,TxnQty,TxnPrice,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))
df_test_Inc <- df_test1[-which(df_test1[,4] == 0),]
df_test_Dec <- df_test1[-which(df_test1[,6] == 0),]
findInterval(abs(df_test1$DecCum[-which(df_test1$DecCum==0)]),df_test1$IncCum[-which(df_test1$IncCum==0)])+1
rm.strat("testport")
stock.str='IBM' # what are we trying it on
currency('USD')
stock(stock.str,currency='USD',multiplier=1)
startDate='2006-12-31'
initEq=1000000
#portfolio.st='testport'
initPortf('testport', symbols=stock.str)
getSymbols(stock.str,from=startDate,index.class=c('POSIXt','POSIXct'))
dfxts1 <- xts(df_test1[-1],index(IBM[1:10,]))
txns <- addTxns('testport',stock.str,dfxts1)
updatePortf('testport')
out <- perTradeStats('testport',stock.str,tradeDef = "increased.to.reduced")
# Checksum End dates
ifelse(sum(out$End - index(dfxts1[which(dfxts1$DecSeq != 0)])) != 0, print("CHECK"), print("OK"))
# Checksum Start dates
idxStart <- drop(coredata(dfxts1$Start[which(dfxts1$DecSeq != 0)]))
new <- dfxts1[which(dfxts1$IncSeq != 0)][idxStart]
ifelse(sum(out$Start - index(new)) != 0, print("CHECK"), print("OK"))
############################################### Scenario 2
Date <- seq.int(1,10,1)
TxnQty <- c(100,50,50,-160,-20,20,30,200,-35,-200)
TxnPrice <- c(101,102,103,104,105,106,107,108,109,110) # just using silly prices
Cum <- c(100,150,200,40,20,40,70,270,235,35)
IncSeq <- c(1,2,3,0,0,4,5,6,0,0)
IncCum <- c(100,150,200,0,0,220,250,450,0,0)
DecSeq <- c(0,0,0,-1,-2,0,0,0,-3,-4)
DecCum <- c(0,0,0,-160,-180,0,0,0,-215,-415)
Start <- c(0,0,0,1,3,0,0,0,3,4)
df_test <- data.frame(cbind(Date,TxnQty,TxnPrice,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))
df_test_Inc <- df_test[-which(df_test[,4] == 0),]
df_test_Dec <- df_test[-which(df_test[,6] == 0),]
findInterval(abs(df_test$DecCum[-which(df_test$DecCum==0)]),df_test$IncCum[-which(df_test$IncCum==0)])+1
# Scenario 2 with addTxns()
rm.strat("testport")
stock.str='IBM' # what are we trying it on
currency('USD')
stock(stock.str,currency='USD',multiplier=1)
startDate='2006-12-31'
initEq=1000000
#portfolio.st='testport'
initPortf('testport', symbols=stock.str)
getSymbols(stock.str,from=startDate,index.class=c('POSIXt','POSIXct'))
dfxts2 <- xts(df_test[-1],index(IBM[1:10,]))
txns <- addTxns('testport',stock.str,dfxts2)
updatePortf('testport')
out <- perTradeStats('testport',stock.str,includeOpenTrade = FALSE,tradeDef = "increased.to.reduced")
# Checksum End dates
ifelse(sum(out$End - index(dfxts2[which(dfxts2$DecSeq != 0)])) != 0, print("CHECK"), print("OK"))
# Checksum Start dates
idxStart <- drop(coredata(dfxts2$Start[which(dfxts2$DecSeq != 0)]))
new <- dfxts2[which(dfxts2$IncSeq != 0)][idxStart]
ifelse(sum(out$Start - index(new)) != 0, print("CHECK"), print("OK"))
############################################### Scenario 3
Date <- seq.int(1,10,1)
TxnQty <- c(100,50,50,-25,-30,-30,25,-45,-40,-55)
TxnPrice <- c(101,102,103,104,105,106,107,108,109,110) # just using silly prices
Cum <- c(100,150,200,0,0,0,225,0,0,0)
IncSeq <- c(1,2,3,0,0,0,4,0,0,0)
IncCum <- c(100,150,200,0,0,0,225,0,0,0)
DecSeq <- c(0,0,0,-1,-2,-3,0,-4,-5,-6)
DecCum <- c(0,0,0,-25,-55,-85,0,-130,-170,-225)
Start <- c(0,0,0,1,1,1,0,1,2,3)
df_test_3 <- data.frame(cbind(Date,TxnQty,TxnPrice,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))
df_test_Inc <- df_test_3[-which(df_test_3[,4] == 0),]
df_test_Dec <- df_test_3[-which(df_test_3[,6] == 0),]
findInterval(abs(df_test_3$DecCum[-which(df_test_3$DecCum==0)]),df_test_3$IncCum[-which(df_test_3$IncCum==0)])+1
# Scenario 3 with addTxns()
rm.strat("testport")
stock.str='IBM' # what are we trying it on
currency('USD')
stock(stock.str,currency='USD',multiplier=1)
startDate='2006-12-31'
initEq=1000000
#portfolio.st='testport'
initPortf('testport', symbols=stock.str)
getSymbols(stock.str,from=startDate,index.class=c('POSIXt','POSIXct'))
dfxts3 <- xts(df_test_3[-1],index(IBM[1:10,]))
txns <- addTxns('testport',stock.str,dfxts3)
updatePortf('testport')
out <- perTradeStats('testport',stock.str,tradeDef = "increased.to.reduced")
# Checksum End dates
ifelse(sum(out$End - index(dfxts3[which(dfxts3$DecSeq != 0)])) != 0, print("CHECK"), print("OK"))
# Checksum Start dates
idxStart <- drop(coredata(dfxts3$Start[which(dfxts3$DecSeq != 0)]))
new <- dfxts3[which(dfxts3$IncSeq != 0)][idxStart]
ifelse(sum(out$Start - index(new)) != 0, print("CHECK"), print("OK"))
@jaymon0703
Copy link
Author

Logic for an "increased.to.decreased" tradeDef method:

Where there is levelling out of a position, perTradeStats (which we use to build our dataframe from which to sample) will have identical start dates for every trade until the position is flat once again, when using the "flat.to.reduced" tradeDef method. So the aim is to add an "increased.to.reduced" tradeDef method with the aim of having at least Average Cost and FIFO accounting methods applicable for defining Round Turn Trades. There are 3 scenarios which could transpire when levelling out of a position:

  1. Unwind qty is identical to initiating qty - this is the simplest case and start date will be the initiation date
Date Trade Cum Inc Seq Inc Cum Dec Seq Dec Cum Start
1 +100 100 1 100 - - -
2 +50 150 2 150 - - -
3 +50 200 3 200 - - -
4 -100 100 - - -1 -100 1
5 -50 50 - - -2 -150 2
6 +50 100 4 250 - - -
7 -50 50 - - -3 -200 3
8 -50 0 - - -4 -250 4
9 +50 50 5 300 - - -
10 -50 0 - - -5 -300 5
  1. Sell more than initiated
Date Trade Cum Inc Seq Inc Cum Dec Seq Dec Cum Start
1 +100 100 1 100 - - -
2 +50 150 2 150 - - -
3 +50 200 3 200 - - -
4 -160 40 - - -1 -160 1
5 -20 20 - - -2 -180 3
6 +20 40 4 220 - - -
7 +30 70 5 250 - - -
8 +200 270 6 450 - - -
9 -35 235 - - -3 -215 3
10 -200 35 - - -4 -415 4

R code for building this dataset:

Date <- seq.int(1,10,1)
Trade <- c(100,50,50,-160,-20,20,30,200,-35,-200)
Cum <- c(100,150,200,40,20,40,70,270,235,35)
IncSeq <- c(1,2,3,0,0,4,5,6,0,0)
IncCum <- c(100,150,200,0,0,220,250,450,0,0)
DecSeq <- c(0,0,0,-1,-2,0,0,0,-3,-4)
DecCum <- c(0,0,0,-160,-180,0,0,0,-215,-415)
Start <- c(0,0,0,1,3,0,0,0,3,4)

df_test <- data.frame(cbind(Date,Trade,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))
df_test_Inc <- df_test[-which(df_test[,4] == 0),]
df_test_Dec <- df_test[-which(df_test[,6] == 0),]

findInterval(abs(df_test$DecCum[-which(df_test$DecCum==0)]),df_test$IncCum[-which(df_test$IncCum==0)])+1

result should be 3,3,4,6 indicating the index of the upper range
note we will have to add logic for the 1st index, which will always equal 1 ie. the first start date

  1. Sell less than initiated
Date Trade Cum Inc Seq Inc Cum Dec Seq Dec Cum Start
1 +100 100 1 100 - - -
2 +50 150 2 150 - - -
3 +50 200 3 200 - - -
4 -25 175 - - 1 -25 1
5 -30 145 - - 2 -55 1
6 -30 115 - - 3 -85 1
7 +25 140 4 225 - - -
8 -45 95 - - 4 -130 1
9 -40 55 - - 5 -170 2
10 -55 0 - - 6 -225 3

R code for building the dataset for scenario 3:

Date <- seq.int(1,10,1)
Trade <- c(100,50,50,-25,-30,-30,25,-45,-40,-55)
Cum <- c(100,150,200,0,0,0,225,0,0,0)
IncSeq <- c(1,2,3,0,0,0,4,0,0,0)
IncCum <- c(100,150,200,0,0,0,225,0,0,0)
DecSeq <- c(0,0,0,-1,-2,-3,0,-4,-5,-6)
DecCum <- c(0,0,0,-25,-55,-85,0,-130,-170,-225)
Start <- c(0,0,0,1,1,1,0,1,2,3)

df_test_3 <- data.frame(cbind(Date,Trade,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))
df_test_Inc <- df_test_3[-which(df_test_3[,4] == 0),]
df_test_Dec <- df_test_3[-which(df_test_3[,6] == 0),]

findInterval(abs(df_test_3$DecCum[-which(df_test_3$DecCum==0)]),df_test_3$IncCum[-which(df_test_3$IncCum==0)])+1

Findings:
Since we are interested in the lagged decreasing-position cumulative quantity, we need to disregard the final element from our output of findInterval. Also, since we are interested in the upper range of the interval, we need to add one to the output. So in scenario 2, our call to findInterval (with +1) returns 3,3,4,6...so we disregard the 6 and 3,3,4 are the indexes of the start dates for the end dates starting from the 2nd end date, respectively.

In scenario 3, the output from our call to findInterval is 1,1,1,2,3,5...so disregarding 5 (ie. the last element, we get 1,1,1,2,3 which are the indexes of the start dates for each of the end dates respectively, starting from the second decreasing trade.

In all cases the index of the start date for the first end date will always be 1.

HAPPY DAYS

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

Scenario 3 with addTxns()

Date <- seq.int(1,10,1)
TxnQty <- c(100,50,50,-25,-30,-30,25,-45,-40,-55)
TxnPrice <- c(101,102,103,104,105,106,107,108,109,110) # just using silly prices
Cum <- c(100,150,200,0,0,0,225,0,0,0)
IncSeq <- c(1,2,3,0,0,0,4,0,0,0)
IncCum <- c(100,150,200,0,0,0,225,0,0,0)
DecSeq <- c(0,0,0,-1,-2,-3,0,-4,-5,-6)
DecCum <- c(0,0,0,-25,-55,-85,0,-130,-170,-225)
Start <- c(0,0,0,1,1,1,0,1,2,3)

df_test_3 <- data.frame(cbind(Date,TxnQty,TxnPrice,Cum,IncSeq,IncCum,DecSeq,DecCum,Start))

suppressWarnings(rm("account.st","portfolio.st","stock.str","stratBBands","startDate","initEq",'start_t','end_t'))
stock.str=c('IBM') # what are we trying it on
for ( st in stock.str) stock(st,currency='USD',multiplier=1)

startDate='2006-12-31'
initEq=1000000

portfolio.st='testport'
initPortf(portfolio.st, symbols=stock.str)
initAcct(account.st,portfolios='bbands')

getSymbols(stock.str,from=startDate,index.class=c('POSIXt','POSIXct'))
dfxts <- xts(df_test_3[-1],index(IBM[1:10,]))

txns <- addTxns('testport',stock.str,dfxts)
updatePortf('testport')
perTradeStats('testport',stock.str,tradeDef = "increased.to.reduced")

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment