[Blotter-commits] r655 - in pkg/FinancialInstrument: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed Jun 29 23:51:27 CEST 2011


Author: gsee
Date: 2011-06-29 23:51:26 +0200 (Wed, 29 Jun 2011)
New Revision: 655

Added:
   pkg/FinancialInstrument/man/fn_SpreadBuilder.Rd
   pkg/FinancialInstrument/man/formatSpreadPrice.Rd
   pkg/FinancialInstrument/man/synthetic.instrument.Rd
Modified:
   pkg/FinancialInstrument/NAMESPACE
   pkg/FinancialInstrument/R/buildSpread.R
   pkg/FinancialInstrument/R/synthetic.R
   pkg/FinancialInstrument/man/buildSpread.Rd
   pkg/FinancialInstrument/man/synthetic.ratio.Rd
Log:
- buildSpread can now build multiple leg spreads.
- fn_Spreadbuilder builds 2 leg spread, but returns multiple columns.
- add formatSpreadPrice function
- add synthetic.instrument function to replace synthetic.ratio
- note synthetic.ratio as deprecated
- export


Modified: pkg/FinancialInstrument/NAMESPACE
===================================================================
--- pkg/FinancialInstrument/NAMESPACE	2011-06-29 20:46:22 UTC (rev 654)
+++ pkg/FinancialInstrument/NAMESPACE	2011-06-29 21:51:26 UTC (rev 655)
@@ -19,7 +19,11 @@
 export(getSymbols.FI)
 export(synthetic)
 export(synthetic.ratio)
+export(synthetic.instrument)
 export(spread)
 export(guaranteed_spread)
+export(butterfly)
+export(formatSpreadPrice)
+export(fn_SpreadBuilder)
 export(volep)
 export(option_series.yahoo)

Modified: pkg/FinancialInstrument/R/buildSpread.R
===================================================================
--- pkg/FinancialInstrument/R/buildSpread.R	2011-06-29 20:46:22 UTC (rev 654)
+++ pkg/FinancialInstrument/R/buildSpread.R	2011-06-29 21:51:26 UTC (rev 655)
@@ -11,72 +11,119 @@
 #' \code{\link{spread}} for instructions on defining the spread
 #' @author bpeterson
 #' @export
-buildSpread<- function(spread_id, ..., Dates = NULL, prefer='Mid.Price', onelot=FALSE, method=c('Close','Midpoint','BA','BB')) {
-    #TODO subset using Dates arg?  or let the +/- operators deal with it?
-    #TODO FIXME put some intelligence in the subsetting and intersection, maybe up front or in a checkData style
-    spread_instr<-try(getInstrument(spread_id))
-    if(inherits(spread_instr,"try-error") | !is.instrument(spread_instr)){
-        stop(paste("Instrument",spread_instr," not found, please create it first."))
-    } 
-    if(!inherits(spread_instr,"spread")) stop (paste("Instrument", spread_id, " is not a spread, please use the symbol of a spread instrument."))
+buildSpread <- function(spread_id, Dates = NULL, onelot=TRUE, prefer = NULL, auto.assign=TRUE, env=.GlobalEnv) #overwrite=FALSE
+{
+##TODO: test something with a different currency    
+    spread_instr <- try(getInstrument(spread_id))
+    if (inherits(spread_instr, "try-error") | !is.instrument(spread_instr)) {
+        stop(paste("Instrument", spread_instr, " not found, please create it first."))
+    }
+    if (!inherits(spread_instr, "synthetic")) 
+        stop(paste("Instrument", spread_id, " is not a synthetic instrument, please use the symbol of a synthetic."))
+    #if (!inherits(try(get(spread_id),silent=TRUE), "try-error") && overwrite==FALSE) #Doesn't work..returns vector of FALSE
+	#stop(paste(spread_instr,' price series already exists. Try again with overwrite=TRUE if you wish to replace it.')) 
 
-    spread_currency<-spread_instr$currency
-    stopifnot(is.currency(spread_currency)) #TODO add assumption of Currency multiplier of 1?
+    spread_currency <- spread_instr$currency
+    stopifnot(is.currency(spread_currency))
     
-    times <- .parseISO8601(Dates)
-    from  <- times$first.time
-    to    <- times$to.time
+    spread_mult <- as.numeric(spread_instr$multiplier)
+    if (is.null(spread_mult) || spread_mult == 0) spread_mult <- 1
+    spread_tick <- spread_instr$tick_size
+  
+    if (!is.null(Dates)) {
+      times <- .parseISO8601(Dates)
+      from <- times$first.time
+      to <- times$last.time
+    }
     
-    # now build each spread factor and add them up
-    spreadseries<-NULL
-    for(i in 1:length(spread_instr$memberlist$members)) {
-        instr<-try(getInstrument(as.character(spread_instr$memberlist$members[i])))
-        if(inherits(instr,"try-error") | !is.instrument(instr)){
-            stop(paste("Instrument",instr," not found, please create it first."))
-        } else {
-            #TODO check to see if instrument is a 'root symbol' instrument like a future or option
-            instr_currency<-instr$currency
-            if(i==1) primary_currency=instr_currency
-            stopifnot(is.currency(instr_currency))
-            if(!all.equal(primary_currency,instr_currency)){
-                instr_currency<-instr$currency
+    spreadseries <- NULL
+    for (i in 1:length(spread_instr$members)) {
+        instr <- try(getInstrument(as.character(spread_instr$members[i])))
+        if (inherits(instr, "try-error") | !is.instrument(instr)) {
+            stop(paste("Instrument", instr, " not found, please create it first."))
+        }
+        else {
+            instr_currency <- instr$currency
+	        if (i == 1) {
+        		primary_currency = instr_currency
+            }
+	        stopifnot(is.currency(instr_currency))
+            if (!all.equal(primary_currency, instr_currency)) {
+                instr_currency <- instr$currency
                 stopifnot(is.currency(instr_currency))
-                exchange_rate<-try(get( paste(primary_currency,instr_currency,sep='')))
-                if(inherits(exchange_rate,"try-error")){
-                    exchange_rate<-try(get( paste(instr_currency,primary_currency,sep='')))
-                    if(inherits(exchange_rate,"try-error")){
-                        stop(paste("Exchange Rate", paste(primary_currency, instr_currency, sep=''), "not found."))    
-                    } else {
+                exchange_rate <- try(get(paste(instr_currency, primary_currency, sep = "")))
+                if (inherits(exchange_rate, "try-error")) {
+                    exchange_rate <- try(get(paste(primary_currency, instr_currency, sep = "")))
+                    if (inherits(exchange_rate, "try-error")) {
+                        stop(paste("Exchange Rate", paste(primary_currency, instr_currency, sep = ""), "not found."))
+                    }
+                    else {
                         exchange_rate <- 1/exchange_rate
-                    }   
+                    }
                 }
-            } else {
-                #currencies of both instruments are the same
-                exchange_rate=1
             }
-            instr_mult<-instr$multiplier
-            instr_ratio<-spread_instr$memberlist$memberratio[i]
-            #TODO get both bid and ask?
-            #instr_prices<-getPrice(get(as.character(spread_instr$memberlist$members[i])),prefer=prefer)
-            instr_prices<-try(get(as.character(spread_instr$memberlist$members[i])))
-            if(inherits(instr_prices,"try-error")){
-                instr_prices<-getSymbols(as.character(spread_instr$memberlist$members[i]),from=from,to=to)
+            else {
+                exchange_rate = 1
             }
-        }        
-        instr_norm<-instr_prices*instr_mult*instr_ratio*exchange_rate
-        colnames(instr_norm)<-paste(as.character(spread_instr$memberlist$members[i]),prefer,sep='.')
-        if(is.null(spreadseries)) spreadseries<-instr_norm else spreadseries=merge(spreadseries,instr_norm)
+            instr_mult <- as.numeric(instr$multiplier)
+            instr_ratio <- spread_instr$memberratio[i]
+            instr_prices <- try(get(as.character(spread_instr$members[i],envir=.GlobalEnv)),silent=TRUE)
+	        # If we were able to find instr_prices in .GlobalEnv, check to make sure there is data between from and to.
+	        #if we couldn't find it in .GlobalEnv or there's no data between from and to, getSymbols
+	        if (inherits(instr_prices, "try-error") || (!is.null(Dates) && length(instr_prices[Dates]) == 0)) {
+                if (is.null(Dates)) {
+                    warning(paste(spread_instr$members[i],"not found in .GlobalEnv, and no Dates supplied. Trying getSymbols defaults.") )
+                    instr_prices <- getSymbols(as.character(spread_instr$members[i]),auto.assign=FALSE)
+                    from <- first(index(instr_prices))
+                    to <- last(index(instr_prices))
+                } else {
+                    warning(paste('Requested data for', spread_instr$members[i], 'not found in .GlobalEnv. Trying getSymbols.'))
+                    instr_prices <- getSymbols(as.character(spread_instr$members[i]), from = from, to = to, auto.assign=FALSE)
+                }
+            }
+	        if (is.null(Dates)) {
+	            from <- first(index(instr_prices))
+	            to <- last(index(instr_prices))
+	        }
+	        instr_prices <- instr_prices[paste(from,to,sep="::")]
+            ##TODO: if length(prefer > 1), use the first value that exists in colnames(instr_prices)
+            ##	i.e. treat prefer as an ordered vector of preferences.
+	        if (is.null(prefer)) { 
+	          if (is.HLC(instr_prices)) { 
+		        pref='Close'
+	          } else
+	          if (has.Mid(instr_prices)) {
+		        pref='Mid'
+	          } else
+	          if (has.Trade(instr_prices)) {
+		        pref='Trade'
+	          } else
+	          if (has.Price(instr_prices)) {
+		        pref='Price'
+	          } else pref=colnames(instr_prices)[1]
+	        } else pref=prefer
+	        if (ncol(instr_prices > 1)) instr_prices <- getPrice(instr_prices,prefer=pref)
+        }
+        instr_norm <- instr_prices * instr_mult * instr_ratio * exchange_rate
+        colnames(instr_norm) <- paste(as.character(spread_instr$members[i]), 
+            prefer, sep = ".")
+        if (is.null(spreadseries)) 
+            spreadseries <- instr_norm
+        else spreadseries = merge(spreadseries, instr_norm)
     }
-
-    # Fill in merged time stamps.  This is correct for Bid and Ask, but may produce bad results with close.
-    for(col in 1:ncol(spreadseries)) {
-        spreadseries[,col]<-na.locf(spreadseries[,col])
-    }    
-    spreadseries<-na.omit(spreadseries)
-    
-    if(onelot) spreadlevel = spreadlevel/spread_instr$memberlist$memberratio[1]
-
-    return(spreadlevel)
+    spreadseries <- na.locf(spreadseries,na.rm=TRUE)
+    spreadlevel = xts(rowSums(spreadseries),order.by=index(spreadseries)) #assumes negative memberratio values for shorts in 'memberratio'
+    if (onelot) 
+        spreadlevel = spreadlevel/abs(spread_instr$memberratio[1]) #abs() takes care of things like a crack spread which is -3:2:1.
+    colnames(spreadlevel) <- paste(spread_id,pref,sep='.')
+    #Divide by multiplier and round according to tick_size of spread_instr
+    if (is.null(spread_tick) || spread_tick == 0) ret <- spreadlevel/spread_mult
+    else ret <- round((spreadlevel / spread_mult) / spread_tick, spread_tick) * spread_tick
+    if (auto.assign) {
+        assign(spread_id, ret, pos=env)
+        ret <- spread_id
+    } else 
+    ret
 }
 
 #' spread builder
@@ -89,45 +136,76 @@
 #' @param unique_method method for making the time series unique, see Details
 #' @author Lance Levenson, Brian Peterson
 #' @export
-fn_SpreadBuilder <- function(prod1, prod2, from, to, ratio, session_times=NULL, unique_method=c('make.index.unique','duplicated','least.liq','price.change'))
+fn_SpreadBuilder <- function(prod1, prod2, ratio=1, from=NULL, to=NULL, session_times=NULL, 
+    unique_method=c('make.index.unique','duplicated','least.liq','price.change'), ...)
 {
+##TODO: don't require from and to to be passed in...use getSymbol defaults.
+##TODO: allow for different methods for calculating Bid and Ask 
+##TODO: Currently we're expecting ratio to be a univariate vector
     #print(paste(date," ",prod1,".",prod2,sep=""))
     
     unique_method<-unique_method[1]
     
+    prod1.instr <- try(getInstrument(prod1))
+    prod2.instr <- try(getInstrument(prod2))
+
+    if (inherits(prod1.instr,'try-error') || 
+        inherits(prod2.instr,'try-error') ||
+        !is.instrument(prod1.instr) ||
+        !is.instrument(prod2.instr) ) stop("both products must be defined as instruments first.")
+
     Data.1 <- NULL
     Data.2 <- NULL
     
-    # put the instrument data into this temporary environment in the function
-    tmpenv<-new.env()
+    Data.1 <- try(get(as.character(prod1),envir=.GlobalEnv),silent=TRUE) 
+    Data.2 <- try(get(as.character(prod2),envir=.GlobalEnv),silent=TRUE)
+    if (inherits(Data.1, "try-error")) Data.1 <- getSymbols(prod1,auto.assign=FALSE,...) #the dots are for from and to    
+    if (inherits(Data.2, "try-error")) Data.2 <- getSymbols(prod2,auto.assign=FALSE,...)
     
+    if ( (is.OHLC(Data.1) && !is.OHLC(Data.2)) || 
+	(is.BBO(Data.1) && !is.BBO(Data.2)) ||
+	(!is.OHLC(Data.1) && is.OHLC(Data.2)) ||
+	(!is.BBO(Data.1) && is.BBO(Data.2)) ) stop('prod1 and prod2 must be the same types of data (BBO,OHLC,etc.)')
     
-    getSymbols(prod1,from=from,to=to,env=tmpenv)
-    Data.1 <- get(prod1,env=tmpenv)        
-    getSymbols(prod2,from=from,to=to,env=tmpenv)
-    Data.2 <- get(prod2,env=tmpenv) 
+    if (is.null(from)) from <- max(index(first(Data.1)),index(first(Data.2)))
+    if (is.null(to)) to <- min(index(last(Data.1)),index(last(Data.2))) 
+    Data.1 <- Data.1[paste(from,to,sep="::")]
+    Data.2 <- Data.2[paste(from,to,sep="::")]
     
-    prod1.instr <- getInstrument(prod1)
-    prod2.instr <- getInstrument(prod2)
+    Mult.1 <- as.numeric(prod1.instr$multiplier) 
+    Mult.2 <- as.numeric(prod2.instr$multiplier) 
     
-    Mult.1 <- prod1.instr$multiplier 
-    Mult.2 <- prod2.instr$multiplier 
-    
     #TODO FIXME we probably need to setSymbolLookup to oanda, and look up the cross rate.
+    #if src is already set, don't reset it
     if (prod1.instr$currency != 'USD'){
         Cur.1 <- get(prod1.instr$currency)
-        Cur.1 <- as.numeric(last(Cur.1[to]))
+        if (!is.null(to)) {
+            Cur.1 <- as.numeric(last(Cur.1[to]))
+        } else Cur.1 <- as.numeric(last(Cur.1))
     } else { Cur.1 <- 1 }
     
     if (prod2.instr$currency != 'USD'){
         Cur.2 <- get(prod2.instr$currency)
-        Cur.2 <- as.numeric(last(Cur.2[to]))
-    } else { Cur.2 <- 1 }
-    
-    
-    M <- merge(Data.1[,c("Bid.Price","Ask.Price")],Data.2[,c("Bid.Price","Ask.Price")])
-    names(M) <- c("Bid.Price.1","Ask.Price.1","Bid.Price.2","Ask.Price.2")
-    
+        if (!is.null(to)) {
+            Cur.2 <- as.numeric(last(Cur.2[to]))
+        } else Cur.2 <- as.numeric(last(Cur.2)) 
+   } else { Cur.2 <- 1 }
+
+    #Determine what type of data it is
+    if (is.OHLC(Data.1) && has.Ad(Data.1)) {
+      	M <- merge(Op(Data.1)[,1],Cl(Data.1)[,1],Ad(Data.1)[,1],Op(Data.2)[,1],Cl(Data.2)[,1],Ad(Data.2)[,1])
+	colnames(M) <- c("Open.Price.1","Close.Price.1","Adjusted.Price.1","Open.Price.2","Close.Price.2","Adjusted.Price.2")
+    } else if(is.OHLC(Data.1)) {
+	M <- merge(Op(Data.1)[,1],Cl(Data.1)[,1],Op(Data.2)[,1],Cl(Data.2)[,1])
+	colnames(M) <- c("Open.Price.1","Close.Price.1","Open.Price.2","Close.Price.2")
+    } else if (is.BBO(Data.1)) {
+	M <- merge(Data.1[,c( grep('Bid',colnames(Data.1),ignore.case=TRUE)[1], 
+			grep('Ask',colnames(Data.1),ignore.case=TRUE)[1])],
+		Data.2[,c(grep('Bid',colnames(Data.1),ignore.case=TRUE)[1],
+			grep('Ask',colnames(Data.2),ignore.case=TRUE)[1])] )
+      colnames(M) <- c("Bid.Price.1","Ask.Price.1","Bid.Price.2","Ask.Price.2")
+    } else M <- merge(Data.1,Data.2)
+
     fn_split <- function(DF)
     {   
         DF.split <- split(DF,"days")
@@ -141,11 +219,12 @@
         }
         #attr(attr(ret,"index"),"tzone") <- "GMT" # no longer needed?
         #attr(ret,".indexTZ") <- "GMT" # no longer needed?
+	colnames(ret) <- colnames(DF)
         ret
     }
     
-    M<- fn_split(M)
-    
+    M <- fn_split(M)
+	
     #can't subset times until after the merge
     if(!is.null(session_times)){
         #Data.1 <- Data.1[time.sub.GMT]
@@ -153,23 +232,49 @@
         M <- M[session_times]
     }
     
-    M$Bid.Price.1 <- M$Bid.Price.1 * Mult.1 * Cur.1 
-    M$Ask.Price.1 <- M$Ask.Price.1 * Mult.1 * Cur.1
-    M$Bid.Price.2 <- M$Bid.Price.2 * Mult.2 * Cur.2
-    M$Ask.Price.2 <- M$Ask.Price.2 * Mult.2 * Cur.2
-    
-    bid <- M$Bid.Price.1 - ratio * M$Ask.Price.2
-    ask <- M$Ask.Price.1 - ratio * M$Bid.Price.2
-    
-    Spread <- cbind(bid,ask)
-    names(Spread) <- c("Bid.Price","Ask.Price")
-    Spread$Mid.Price <- (Spread$Bid.Price + Spread$Ask.Price) / 2
-    
+    if( is.OHLC(Data.1) ) {
+      M$Open.Price.1 <- M$Open.Price.1 * Mult.1 * Cur.1 
+      M$Close.Price.1 <- M$Close.Price.1 * Mult.1 * Cur.1
+      M$Open.Price.2 <- M$Open.Price.2 * Mult.2 * Cur.2
+      M$Close.Price.2 <- M$Close.Price.2 * Mult.2 * Cur.2
+      
+      open <- M$Open.Price.1 - M$Open.Price.2
+      close <- M$Close.Price.1 - M$Close.Price.2
+
+      Spread <- cbind(open,close)
+      colnames(Spread) <- c('Open.Price','Close.Price')
+      if (has.Ad(Data.1)) {
+	M$Adjusted.Price.1 <- M$Adjusted.Price.1 * Mult.1 * Cur.1
+	M$Adjusted.Price.2 <- M$Adjusted.Price.2 * Mult.2 * Cur.2
+	Spread$Adjusted.Price <- M$Adjusted.Price.1 - M$Adjusted.Price.2
+      }
+      #Spread$Mid.Price <- (Spread$Open.Price + Spread$Close.Price) / 2
+    } else
+    if (is.BBO(Data.1) ) {
+      M$Bid.Price.1 <- M$Bid.Price.1 * Mult.1 * Cur.1 
+      M$Ask.Price.1 <- M$Ask.Price.1 * Mult.1 * Cur.1
+      M$Bid.Price.2 <- M$Bid.Price.2 * Mult.2 * Cur.2
+      M$Ask.Price.2 <- M$Ask.Price.2 * Mult.2 * Cur.2
+      ##TODO: Expand this to work with multiple legs
+      bid <- M$Bid.Price.1 - ratio * M$Ask.Price.2
+      ask <- M$Ask.Price.1 - ratio * M$Bid.Price.2
+      
+      Spread <- cbind(bid,ask)
+      names(Spread) <- c("Bid.Price","Ask.Price")
+      Spread$Mid.Price <- (Spread$Bid.Price + Spread$Ask.Price) / 2
+    } else {
+    #univariate spread.  Call buildSpread2?
+      if (ncol(M) > 2) stop('Unrecognized column names.')
+      Spread <- M[,1] - ratio * M[,2]
+      colnames(Spread) <- 'Price'
+    }
+##TODO: Test with symbols where each symbol has data on a day that the other one doesn't 
+##TODO: Add a method that merges Data.1 and Data.2 with all=FALSE and use that index to subset
     switch(unique_method,
             make.index.unique = {Spread<-make.index.unique(Spread)},
             least.liq = {
                 #determine the least liquid
-                idx1 <- index(na.omit(getPrice(Data.1)))
+                idx1 <- index(na.omit(getPrice(Data.1))) 
                 idx2 <- index(na.omit(getPrice(Data.2)))
                 if(length(idx1)<length(idx2)) idx<-idx1 else idx <- idx2
                 
@@ -186,10 +291,18 @@
                 
             }
     )
-    
-    return(Spread)  
+##TODO: look to see if there is an instrument defined for this spread (using whatever is the spread naming convention).
+## If it is not defined, then define it, adding fn_SpreadBuilder to the type, or indicating in some other way that it was
+## auto-defined.
+
+    Spread  
 }
 
+formatSpreadPrice <- function(x,multiplier=1,tick_size=0.01) {
+  x <- x / multiplier
+  round( x / tick_size) * tick_size
+}
+
 ###############################################################################
 # R (http://r-project.org/) Instrument Class Model
 #

Modified: pkg/FinancialInstrument/R/synthetic.R
===================================================================
--- pkg/FinancialInstrument/R/synthetic.R	2011-06-29 20:46:22 UTC (rev 654)
+++ pkg/FinancialInstrument/R/synthetic.R	2011-06-29 21:51:26 UTC (rev 655)
@@ -80,25 +80,91 @@
     synthetic(primary_id=primary_id , currency=currency , multiplier=multiplier , identifiers = identifiers, members=memberlist , memberratio=memberratio, ...=... ,type=type, tick_size=tick_size)
 }
 
+synthetic.instrument <- function (primary_id, currency, members, memberratio, ..., multiplier = 1, tick_size=NULL, 
+    identifiers = NULL, type = c("synthetic.instrument", "synthetic", "instrument")) 
+{
+    if (!is.list(members)) {
+        if (length(members) != length(memberratio) | length(members) < 
+            2) {
+            stop("length of members and memberratio must be equal, and contain two or more instruments")
+        }
+        else {
+            memberlist <- list(members = members, memberratio = memberratio, 
+                currencies = vector(), memberpositions = NULL)
+        }
+        for (member in members) {
+            tmp_symbol <- member
+            tmp_instr <- try(getInstrument(member))
+            if (inherits(tmp_instr, "try-error") | !is.instrument(tmp_instr)) {
+                message(paste("Instrument", tmp_symbol, " not found, using currency of", 
+                  currency))
+                memberlist$currencies[member] <- currency
+            }
+            else {
+                memberlist$currencies[member] <- tmp_instr$currency
+            }
+        }
+        names(memberlist$members) <- memberlist$members
+        names(memberlist$memberratio) <- memberlist$members
+        names(memberlist$currencies) <- memberlist$members
+    }
+    else {
+        warning("passing in members as a list not fully tested")
+        memberlist = members
+    }
+    if (is.null(currency)) 
+        currency <- as.character(memberlist$currencies[1])
+    synthetic(primary_id = primary_id, currency = currency, multiplier = multiplier, 
+        identifiers = identifiers, memberlist = memberlist, memberratio = memberratio, tick_size=tick_size,
+        ... = ..., members = members, type = type)
+}
+
+
+
 #' @export
-spread <- function(primary_id , currency=NULL , members, memberratio, ..., multiplier=1, identifiers = NULL)
+spread <- function (primary_id, currency = NULL, members, memberratio, tick_size=NULL,
+    ..., multiplier = 1, identifiers = NULL) 
 {
-    synthetic.ratio(primary_id=primary_id , currency=currency , members=members, memberratio=memberratio, multiplier=multiplier, identifiers = identifiers, ...=..., type=c("spread","synthetic.ratio","synthetic","instrument"))
+    synthetic.instrument(primary_id = primary_id, currency = currency, 
+      members = members, memberratio = memberratio, ...=..., tick_size=tick_size,
+      multiplier = multiplier, identifiers = identifiers, 
+      type = c("spread", "synthetic.instrument", "synthetic", "instrument"))
 }
 
+
+#TODO: butterfly can refer to expirations (futures) or strikes (options)
+butterfly <- function(primary_id, currency=NULL, members,tick_size=NULL, identifiers=NULL, ...)
+{
+##TODO: A butterfly could either have 3 members that are outrights, or 2 members that are spreads
+  if (length(members) == 3) {
+    synthetic.instrument(primary_id=primary_id,currency=currency,members=members,
+	    memberratio=c(1,-2,1), multiplier=1, tick_size=tick_size,
+	    identifiers=NULL, ...=..., type = c('butterfly','spread','synthetic.instrument',
+	    'synthetic','instrument'))
+  } else if (length(members) == 2) {
+      stop('butterfly currently only supports 3 leg spreads (i.e. no spread of spreads yet.)')
+
+  } else stop('A butterfly must either have 3 outright legs or 2 spread legs') 
+  
+}
+
+
 #' @export
-guaranteed_spread <- function(primary_id , currency , members=NULL, memberratio=c(1,1), ..., multiplier=1, identifiers = NULL)
+guaranteed_spread <- function (primary_id, currency, members = NULL, memberratio = c(1,-1), ..., 
+    multiplier = 1, identifiers = NULL, tick_size=NULL)
 {
-    if (hasArg(suffix_id)){
-        suffix_id<-match.call(expand.dots=TRUE)$suffix_id  
-        id<-paste(primary_id, suffix_id,sep="_")
-    } else id<-primary_id 
-
-    
-    if(is.null(members) && hasArg(suffix_id)){
-        #make.names uses a dot to replace illegal chars like the '-', 
-        members<-unlist(strsplit(suffix_id,"[-;:_,\\.]")) # clean up the list to something we can use  
-        members<-paste(primary_id,members,sep='_') # construct a member vector appropriate for a guaranteed spread
+    if (hasArg(suffix_id)) {
+        suffix_id <- match.call(expand.dots = TRUE)$suffix_id
+        id <- paste(primary_id, suffix_id, sep = "_")
     }
-    synthetic.ratio(primary_id=id , currency=currency , members=members, memberratio=memberratio, multiplier=multiplier, identifiers = NULL, ...=..., type=c("guaranteed_spread","spread","synthetic.ratio","synthetic","instrument"))
+    else id <- primary_id
+    if (is.null(members) && hasArg(suffix_id)) {
+        members <- unlist(strsplit(suffix_id, "[-;:_,\\.]"))
+        members <- paste(primary_id, members, sep = "_")
+    }
+    synthetic.instrument(primary_id = id, currency = currency, members = members, 
+	memberratio = memberratio, multiplier = multiplier, identifiers = NULL, 
+	tick_size=tick_size, ... = ..., type = c("guaranteed_spread", "spread", 
+	"synthetic.instrument", "synthetic", "instrument"))
 }
+

Modified: pkg/FinancialInstrument/man/buildSpread.Rd
===================================================================
--- pkg/FinancialInstrument/man/buildSpread.Rd	2011-06-29 20:46:22 UTC (rev 654)
+++ pkg/FinancialInstrument/man/buildSpread.Rd	2011-06-29 21:51:26 UTC (rev 655)
@@ -1,14 +1,61 @@
 \name{buildSpread}
 \alias{buildSpread}
-\title{construct a price/level series for a spread...}
-\usage{buildSpread(spread_id, ..., Dates = NULL, prefer='Mid.Price', onelot=FALSE, method=c('Close','Midpoint','BA','BB'))}
-\description{construct a price/level series for a spread}
-\details{this function should provide a generic spread series builder.}
-\seealso{\code{\link{spread}} for instructions on defining the spread}
-\author{bpeterson}
-\arguments{\item{spread_id}{string descrining the primary_id of an instrument of type 'spread}
-\item{...}{any other passthru parameters}
-\item{Dates}{date range to subset on, currently not implemented}
-\item{prefer}{preferred column to use}
-\item{onelot}{TRUE/FALSE, if TRUE, will divide by the number of units of the front leg to get a 'onelot'}
-\item{method}{method for pricing: Close, Midpoint BA, BB} }
+%- Also NEED an '\alias' for EACH other topic documented here.
+\title{
+build price series for pre-defined multi-leg spread instrument
+}
+\description{
+build price series for spreads, butterflies, or other synthetic instruments, using metadata of a previously defined synthetic instrument.
+}
+\usage{
+buildSpread(spread_id, Dates = NULL, onelot=TRUE, prefer = NULL, auto.assign=TRUE, env=.GlobalEnv)
+}
+%- maybe also 'usage' for other objects documented here.
+\arguments{
+  \item{spread_id}{
+The name of the instrument that contains members and memberratio  
+}
+  \item{Dates}{
+date range to subset on; currently not implemented
+}
+  \item{onelot}{
+Should the series be divided by the first leg's ratio 
+}
+  \item{prefer}{
+price column to use to build structure.
+}
+  \item{auto.assign}{assign the spread? If FALSE, the xts object will be returned}
+  \item{env}{environment to assign spread into.}
+}
+\details{
+The spread and all legs must be defined instruments.
+
+This function can build multileg spreads such as calendars, butterflies, condors, etc. However, the returned series will be univariate. It does not build Bid Ask Mid data like fn_SpreadBuilder2 does.
+}
+\value{
+If \code{auto.assign} is FALSE, a univariate xts object 
+otherwise, the xts object will be assigned to \code{spread_id} and the \code{spread_id} will be returned.
+}
+\author{
+Brian Peterson, Garrett See
+}
+\note{
+This function requires that the spread to be build be defined using one of the twsInstrument functions. Specifically, synthetic.ratio from FinancialInstrument should not be used. synthetic.ratio stores memberratios deeper inside the instrument (instr$members$members instead of instr$members)
+}
+
+%% ~Make other sections like Warning with \section{Warning }{....} ~
+
+\seealso{
+fn_SpreadBuilder
+}
+\examples{
+\dontrun{
+currency("USD")
+stock("SPY","USD",1)
+stock("DIA","USD",1)
+spread("SPYDIA", "USD", c("SPY","DIA"),c(1,-1))
+buildSpread('SPYDIA')
+head(SPYDIA)
+}
+}
+

Added: pkg/FinancialInstrument/man/fn_SpreadBuilder.Rd
===================================================================
--- pkg/FinancialInstrument/man/fn_SpreadBuilder.Rd	                        (rev 0)
+++ pkg/FinancialInstrument/man/fn_SpreadBuilder.Rd	2011-06-29 21:51:26 UTC (rev 655)
@@ -0,0 +1,71 @@
+\name{fn_SpreadBuilder}
+\alias{fn_SpreadBuilder}
+%- Also NEED an '\alias' for EACH other topic documented here.
+\title{
+calculate prices of a spread from 2 instruments
+}
+\description{
+Calculates all price columns of a spread given 2 instruments
+}
+\usage{
+fn_SpreadBuilder(prod1, prod2, ratio = 1, from = NULL, to = NULL, session_times = NULL, unique_method = c("make.index.unique", "duplicated", "least.liq", "price.change"), ...)
+}
+%- maybe also 'usage' for other objects documented here.
+\arguments{
+  \item{prod1}{
+chr name of instrument that will be the 1st leg of a 2 leg spread
+}
+  \item{prod2}{
+chr name of instrument that will be the 2nd leg of a 2 leg spread
+}
+  \item{ratio}{
+hedge ratio.
+}
+  \item{from}{
+from Date to pass through to getSymbols if needed.
+}
+  \item{to}{
+to Date to pass through to getSymbols if needed.
+}
+  \item{session_times}{
+session_times ISO-8601 time subset for the session time, in GMT, in the format 'T08:00/T14:59'
+}
+  \item{unique_method}{
+method for making the time series unique
+}
+  \item{\dots}{
+any other passthrough parameters
+}
+}
+\details{ 
+Before calling, both products must be defined as instruments.  
+
+It will try to get data for \code{prod1} and \code{prod2} from .GlobalEnv.  
+If it cannot find the data, it will get it with a call to getSymbols. 
+
+Prices are multiplied by multipliers and exchange rates to get notional values in USD using the most recent exchange rate.
+The second legs new values are multiplied by the ratio. Then the difference is taken between the new values for leg1 and the new values for leg2.
+
+\sQuote{make.index.unique} uses the xts function \code{make.index.unique} 
+\sQuote{least.liq} subsets the spread time series, by using the timestamps of the leg that has the fewest rows.
+\sQuote{duplicated} removes any duplicate indexes.
+\sQuote{price.change} only return rows where there was a price change in the Bid, Mid or Ask Price of the spread.
+}
+\value{
+an xts object with
+Bid, Ask, Mid columns, 
+or Open, Close, Adjusted columns, 
+or Open, Close columns.
+or Price column.
+}
+\author{
+Lance Levenson, Brian Peterson, Garrett See
+}
+\note{
+Currently, this doesn't really support multi-currency spreads.  If an instrument is not denominated in USD, it will try to get data for that currency from the .GlobalEnv, but rarely would you have data stored in object called e.g. \sQuote{EUR}.  So, it probably won't find the data. This should be updated to look for exchange rates either by simply looking for both e.g.\sQuote{EURUSD} and \sQuote{USDEUR}, or by getSymbols.oanda. Also, a parameter should be added for spread currency instead of requiring that the spread be denominated in USD. Finally, it should use all exchange rate data to build the spread instead of the most recent exchange rate (at the very least, it is currently using data from the future to calculate spread prices for multi-currency products.)
+}
+
+\seealso{
+buildSpread, synthetic.instrument, formatSpreadPrice
+}
+

Added: pkg/FinancialInstrument/man/formatSpreadPrice.Rd
===================================================================
--- pkg/FinancialInstrument/man/formatSpreadPrice.Rd	                        (rev 0)
+++ pkg/FinancialInstrument/man/formatSpreadPrice.Rd	2011-06-29 21:51:26 UTC (rev 655)
@@ -0,0 +1,33 @@
+\name{formatSpreadPrice}
+\alias{formatSpreadPrice}
+%- Also NEED an '\alias' for EACH other topic documented here.
+\title{
+format the price of a synthetic instrument
+}
+\description{
+Divides the notional spread price by the spread multiplier and rounds prices to the nearest tick_size.
+}
+\usage{
+formatSpreadPrice(x, multiplier = 1, tick_size = 0.01)
+}
+%- maybe also 'usage' for other objects documented here.
+\arguments{
+  \item{x}{
+xts price series
+}
+  \item{multiplier}{
+numeric multiplier (e.g. 1000 for crack spread to get from $ to $/bbl)
+}
+  \item{tick_size}{
+minimum price change of the spread
+}
+}
+\value{
+price series of same length as \code{x}
+}
+\author{
+Garrett See
+}\seealso{
+buildSpread, fn_SpreadBuilder
+}
+

Added: pkg/FinancialInstrument/man/synthetic.instrument.Rd
===================================================================
--- pkg/FinancialInstrument/man/synthetic.instrument.Rd	                        (rev 0)
+++ pkg/FinancialInstrument/man/synthetic.instrument.Rd	2011-06-29 21:51:26 UTC (rev 655)
@@ -0,0 +1,82 @@
+\name{synthetic.instrument}
+\alias{synthetic.instrument}
+\alias{synthetic}
+\alias{spread}
+\alias{guaranteed_spread}
+\alias{butterfly}
+
+%- Also NEED an '\alias' for EACH other topic documented here.
+\title{
+synthetic instrument contructors
+}
+\description{
+define spreads, guaranteed_spreads, butterflies and other synthetic instruments
+}
+\usage{
+synthetic.instrument(primary_id, currency, members, memberratio, ..., multiplier = 1, tick_size = NULL, identifiers = NULL, type = c("synthetic.instrument", "synthetic", "instrument"))
+synthetic(primary_id , currency , multiplier=1, identifiers = NULL, ..., members=NULL, type=c("synthetic", "instrument"))
+spread(primary_id, currency = NULL, members, memberratio, tick_size=NULL,
+    ..., multiplier = 1, identifiers = NULL) 
+guaranteed_spread(primary_id, currency, members = NULL, memberratio = c(1,-1), ..., 
+    multiplier = 1, identifiers = NULL, tick_size=NULL)
+}
+%- maybe also 'usage' for other objects documented here.
+\arguments{
+  \item{primary_id}{
+chr string of primary identifier of instrument to be defined.
+}
+  \item{currency}{
+chr string name of currency denomination
+}
+  \item{members}{
+vector of primary_ids of member instruments
+}
+  \item{memberratio}{
+vector of weights for each leg. negative numbers for selling.
+}
+  \item{\dots}{
+any other passthrough parameters
+}
+  \item{multiplier}{
+multiplier of the spread.
+}
+  \item{tick_size}{
+minimum price change of spread
+}
+  \item{identifiers}{
+identifiers
+}
+  \item{type}{
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/blotter -r 655


More information about the Blotter-commits mailing list