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

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Sep 5 06:31:51 CEST 2011


Author: gsee
Date: 2011-09-05 06:31:48 +0200 (Mon, 05 Sep 2011)
New Revision: 749

Added:
   pkg/FinancialInstrument/man/getRoot.Rd
Modified:
   pkg/FinancialInstrument/DESCRIPTION
   pkg/FinancialInstrument/NAMESPACE
   pkg/FinancialInstrument/R/buildSpread.R
   pkg/FinancialInstrument/R/format_id.R
   pkg/FinancialInstrument/R/instrument.R
   pkg/FinancialInstrument/R/parse_id.R
   pkg/FinancialInstrument/R/synthetic.R
   pkg/FinancialInstrument/man/synthetic.instrument.Rd
Log:
 - parse_id/parse_suffix now support butterflies 
 - parse_suffix now supports option_id with 8 digit strike
 - add getRoot function (and aliases get_future and get_option) and use in future_series and option_series
 - synthetic wrappers will now make_spread_id if primary_id is not provided.
 - most synthetic wrappers will now use the currency of the 1st member if currency is not provided
 - make_spread_id now passes what it made through make.names
 - synthetic.instrument can now handle members that is list of instruments, or memberlist, or vector of names of instruments
 - guaranteed_spread can now be called with only members arg being specified, or with only primary_id
 - sort_id now returns NULL instead of error when called with ids=NULL


Modified: pkg/FinancialInstrument/DESCRIPTION
===================================================================
--- pkg/FinancialInstrument/DESCRIPTION	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/DESCRIPTION	2011-09-05 04:31:48 UTC (rev 749)
@@ -11,7 +11,7 @@
     meta-data and relationships. Provides support for
     multi-asset class and multi-currency portfolios.  
     Still in heavy development.
-Version: 0.5
+Version: 0.5.1
 URL: https://r-forge.r-project.org/projects/blotter/
 Date: $Date$
 Depends:

Modified: pkg/FinancialInstrument/NAMESPACE
===================================================================
--- pkg/FinancialInstrument/NAMESPACE	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/NAMESPACE	2011-09-05 04:31:48 UTC (rev 749)
@@ -17,6 +17,7 @@
 export(future)
 export(future_series)
 export(getInstrument)
+export(getRoot)
 export(getSymbols.FI)
 export(guaranteed_spread)
 export(instrument)

Modified: pkg/FinancialInstrument/R/buildSpread.R
===================================================================
--- pkg/FinancialInstrument/R/buildSpread.R	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/R/buildSpread.R	2011-09-05 04:31:48 UTC (rev 749)
@@ -409,7 +409,8 @@
 	#if (is.character(format)) suff <- paste(sapply(strsplit(suff,"\\.")[[1]], format_id, format=format, parse='suffix'), collapse=".")
     if (!is.null(format) && is.character(format)) 
 		suff <- paste(format_id(strsplit(suff,"\\.")[[1]], format=format, parse='suffix'), collapse=".")
-    return(paste(root,suff, sep="_"))        
+    id <- paste(root,suff, sep="_")
+    return(make.names(id))
 }
 
 

Modified: pkg/FinancialInstrument/R/format_id.R
===================================================================
--- pkg/FinancialInstrument/R/format_id.R	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/R/format_id.R	2011-09-05 04:31:48 UTC (rev 749)
@@ -216,6 +216,7 @@
 #' sort_ids(ids)
 #' @export
 sort_ids <- function(ids, ...) {
+    if (is.null(ids)) return(NULL)
     f <- function(x, ...) {
         pid <- parse_id(x, ...)
         as.Date(paste(pid$year,pid$month,15,sep=''),format="%Y%b%d")

Modified: pkg/FinancialInstrument/R/instrument.R
===================================================================
--- pkg/FinancialInstrument/R/instrument.R	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/R/instrument.R	2011-09-05 04:31:48 UTC (rev 749)
@@ -167,6 +167,59 @@
     instrument(primary_id=primary_id , currency=currency , multiplier=multiplier , tick_size=tick_size, identifiers = identifiers, ... , type="future", underlying_id=underlying_id, assign_i=TRUE )
 }
 
+#' Get the root contract specs for an instrument
+#' 
+#' Get a \code{future} or \code{option} object
+#' 
+#' \code{get_option} and \code{get_future} are wrappers, and they are called internally by \code{\link{future_series}} and \code{\link{option_series}}
+#' 
+#' \code{\link{future}} and \code{\link{option}} objects may have a primary_id that 
+#' begins with 1 or 2 dots (in order to avoid naming conflics).  For example, the root specs
+#' for options (or futures) on the stock with ticker "SPY" may be stored with a primary_id 
+#' of "SPY", ".SPY", or "..SPY"
+#'
+#' This function will try calling \code{\link{getInstrument}} using each possible primary_id
+#' until it finds the instrument that is of appropriate \code{type}.
+#' @param root_id string (e.g. "ES", ".ES", or "..ES" for e-mini S&P 500 futures)
+#' @param type character. type of instrument to look for ("future" or "option"). Alternatively, can be numeric: 1 for "future" or 2 for "option"
+#' @return an object of class \code{type}
+#' @author Garrett See
+#' @seealso \code{\link{getInstrument}}
+#' @examples
+#' \dontrun{
+#' option('.SPY',currency("USD"),100,underlying_id=stock("SPY","USD"))
+#' future("..SPY","USD", 100, underlying_id="SPY")
+#' getRoot("SPY", 'future')
+#' getRoot("SPY", 'option')
+#' }
+#' @export
+getRoot <- function(root_id, type=c('future','option')) {
+    if (is.numeric(type)) type <- c('future','option')[type]
+    type <- type[[1]]    
+    #first try to get the instrument with primary_id == root_id, and return it if successful
+    contract <- try(getInstrument(root_id, silent=TRUE))
+    if (inherits(contract, type)) return(contract)
+    #if not successful, strip out the dots and add them back 1 at a time to the beginning of root_id
+    root_id <- gsub("\\.","",root_id)
+    contract<-try(getInstrument(root_id,silent=TRUE))
+    if(!inherits(contract,type)) {
+        contract<-try(getInstrument(paste(".",root_id,sep=""),silent=TRUE))
+        if(!inherits(contract,type)) {
+            contract<-try(getInstrument(paste("..",root_id,sep=""),silent=TRUE))
+            if (!inherits(contract,type)) {
+                stop(paste(type, "contract spec must be defined first"))
+            }
+        }
+    }
+    contract
+}
+
+#' @rdname getRoot
+get_option <- function(root_id) getRoot(root_id, type='option')
+#' @rdname getRoot
+get_future <- function(root_id) getRoot(root_id, type='future')
+
+
 #' constructors for series contracts on instruments such as options and futures
 #' 
 #' constructors for series contracts on instruments such as options and futures
@@ -233,15 +286,7 @@
     if (!identical(integer(0), grep("NA",expires))) expires <- NULL
   }
 
-  contract<-try(getInstrument(root_id,silent=TRUE))
-  if(!inherits(contract,"future")) {
-      contract<-try(getInstrument(paste(".",root_id,sep=""),silent=TRUE))
-      if(!inherits(contract,"future")) {
-          contract<-try(getInstrument(paste("..",root_id,sep=""),silent=TRUE))
-          if (!inherits(contract,"future")) 
-            stop("futures contract spec must be defined first")
-      }
-  }
+  contract<-get_future(root_id)
   
   # TODO add check for Date equivalent in first_traded and expires
 
@@ -324,15 +369,7 @@
         if (!identical(integer(0), grep("NA",expires))) 
             stop("must provide 'expires' formatted '%Y-%m-%d', or a 'suffix_id' from which to infer 'expires'")
     }
-    contract<-try(getInstrument(root_id,silent=TRUE))
-    if(!inherits(contract,"option")) {
-        contract<-try(getInstrument(paste(".",root_id,sep=""),silent=TRUE))
-        if(!inherits(contract,"option")) {
-            contract<-try(getInstrument(paste("..",root_id,sep=""),silent=TRUE))
-            if(!inherits(contract,"option")) 
-                stop("options contract spec must be defined first")
-        }
-    }    
+    contract<-get_option(root_id)
     
     ## with options series we probably need to be more sophisticated,
     ## and find the existing series from prior periods (probably years)

Modified: pkg/FinancialInstrument/R/parse_id.R
===================================================================
--- pkg/FinancialInstrument/R/parse_id.R	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/R/parse_id.R	2011-09-05 04:31:48 UTC (rev 749)
@@ -27,18 +27,38 @@
 parse_id <- function(x, silent=TRUE, root=NULL) {
     sufftype <- TRUE #will we use the type given by parse_suffix, or overwrite it with e.g. 'exchange_rate'
     if (!is.null(root)) {
-            suffix <- gsub(root,"",x) #turns ESU1 into U1, or ES_U11 into _U11 
-            suffix <- gsub("_","",suffix) #take out the underscore if there is one
+        suffix <- gsub(root,"",x) #turns ESU1 into U1, or ES_U11 into _U11 
+        suffix <- gsub("_","",suffix) #take out the underscore if there is one
     } else if (identical(integer(0), grep("[0-9]",x))) { 
         #if there are no numbers in the id, then it has no year, so it is not a recognized future or option
-        root <- x
-        suffix <- ""
-        if (nchar(x) == 6) {
-            if (is.instrument(getInstrument(substr(x,1,3),silent=TRUE)) 
-                && is.instrument(getInstrument(substr(x,4,6),silent=TRUE))) {
-                type <- c('exchange_rate', 'root')
-                sufftype <- FALSE
+        if (identical(all.equal(nchar(x) - nchar( gsub("\\.","",x)),1), TRUE)) { 
+            #only 1 dot, so it's not a fly
+            #SPY.DIA, EUR.USD, SPY110917C122.5, T2010917P25
+            if (suppressWarnings(!is.na(as.numeric(strsplit(x,"\\.")[[1]][2])))) { #probably an option with a decimal in the strike
+                #if we take out all the numbers, periods, and dashes, 
+                #we should be left with the ticker and either "C" or "P"                
+                root <- gsub("[0-9.-]","",x) #now it looks like SPYC or TP
+                root <- substr(root, 1,nchar(root)-1)
+                suffix <- gsub(root,"",x) #whatever isn't the root
+            } else { #probably a synthetic: SPY.DIA, GLD.EUR
+                suffix <- x
+                root <- x
             }
+        } else if (identical(all.equal(nchar(x) - nchar( gsub("\\.","",x)),2), TRUE)) { 
+            #2 dots, so we'll treat it as a fly, although it could be a basket
+            #SPY.DIA.QQQ, 
+            suffix <- x
+            root <- x
+        } else {
+            root <- x
+            suffix <- ""
+            if (nchar(x) == 6) {
+                if (is.instrument(getInstrument(substr(x,1,3),silent=TRUE)) 
+                    && is.instrument(getInstrument(substr(x,4,6),silent=TRUE))) {
+                    type <- c('exchange_rate', 'root')
+                    sufftype <- FALSE
+                }
+            }
         }
     } else if (identical(x, gsub('_','',x))) { #no underscore; have to guess what is root and what is suffix       
         hasdot <- !identical(integer(0),grep("\\.",x))        
@@ -50,19 +70,6 @@
         } else if (nchar(x) < 9 && !hasdot) { #assume it's a future like ESU1 or ESU11
             root <- substr(x,1,2)
             suffix <- substr(x,3,nchar(x))
-        } else if (identical(all.equal(nchar(x) - nchar( gsub("\\.","",x)),1), TRUE)) { 
-            #only 1 dot, so it's not a fly
-            #SPY.DIA, EUR.USD, SPY110917C122.5, T2010917P25
-            if (!is.na(as.numeric(strsplit(x,"\\.")[[1]][2]))) { #probably an option with a decimal in the strike
-                #if we take out all the numbers, periods, and dashes, 
-                #we should be left with the ticker and either "C" or "P"                
-                root <- gsub("[0-9.-]","",x) #now it looks like SPYC or TP
-                root <- substr(root, 1,nchar(root)-1)
-                suffix <- gsub(root,"",x) #whatever isn't the root
-            } else { #probably a synthetic: SPY.DIA, GLD.EUR
-                suffix <- x
-                root <- x
-            }
         } else {
             root <- gsub("[0-9.-]","",x) #now it looks like SPYC or TP
             root <- substr(root, 1,nchar(root)-1)
@@ -142,7 +149,7 @@
         format <- 'cc'
     } else if (nchar(x) > 7 && (any(substr(x,7,7) == c("C","P")) || any(substr(x,9,9) == c("C","P"))) ) {
         # if the 7th or 9th char is a "C" or "P", it's an option
-        # 110917C125 or 20110917C125
+        # 110917C125 or 20110917C125 or 110917C00012500 or 20110917C00012500
         hasdot <- !identical(integer(0),grep("\\.",x))
         if (!hasdot
             || (hasdot 
@@ -155,6 +162,7 @@
                 month <- toupper(month.abb[as.numeric(substr(x,3,4))])
                 year <- 2000 + as.numeric(substr(x,1,2))
                 strike <- as.numeric(substr(x,8,nchar(x)))
+                if (nchar(x) >= 15) strike <- strike/100                 
                 right <- substr(x,7,7)
                 format <- 'opt2'    
             } else if (any(substr(x,9,9) == c("C","P"))) {
@@ -162,6 +170,7 @@
                 month <- toupper(month.abb[as.numeric(substr(x,5,6))])
                 year <- as.numeric(substr(x,1,4))
                 strike <- as.numeric(substr(x,10,nchar(x)))
+                if (nchar(x) >= 15) strike <- strike/100
                 right <- substr(x,9,9)
                 format <- 'opt4'
             } else stop("how did you get here?")
@@ -184,6 +193,24 @@
             } else { 
                 type=c('calendar','spread')
             }
+        } else if (identical(all.equal(nchar(x) - nchar(gsub("\\.","",x)),2), TRUE)) { #2 dots; it's a fly
+            #U1.Z1.H2, U11.Z11.H12, SPY.DIA.QQQ
+            s <- strsplit(x, "\\.")[[1]]
+            s1 <- try(parse_suffix(s[1],silent=TRUE),silent=TRUE)
+            s2 <- try(parse_suffix(s[2],silent=TRUE),silent=TRUE)
+            s3 <- try(parse_suffix(s[3],silent=TRUE),silent=TRUE)
+            if (inherits(s1,'try-error')) s1 <- parse_id(s[1],silent=TRUE)
+            if (inherits(s2,'try-error')) s2 <- parse_id(s[2],silent=TRUE)
+            if (inherits(s3,'try-error')) s3 <- parse_id(s[3],silent=TRUE)          
+            if (all(c(s1$type,s2$type,s3$type) == 'root')) {
+                type='synthetic' #don't really know if it's fly-like or a basket
+            } else { 
+                type=c('butterfly','spread')
+            }
+            format <- unique(c(s1$format, s2$format, s3$format))
+        } else {
+            if (!silent) warning("limited functionality for suffix that implies more than 3 instruments")
+            type='synthetic' #condors, baskets, strips, packs/bundles,     
         }
     ##End check for suffixes with a dot
     } else if (any(substr(x,1,2) == c("1C","1D"))) { # Single-stock future (SSF) 
@@ -207,7 +234,7 @@
             format <- 'CY'
         } else if (is.na(as.numeric(x))) type <- 'root'
     } else if (nchar(x) == 3) { #U11
-        if (substr(x,1,1) %in% M2C() && !is.na(as.numeric(substr(x,2,3)))) {
+        if (substr(x,1,1) %in% M2C() && suppressWarnings(!is.na(as.numeric(substr(x,2,3))))) {
             type <- c("outright","future")
             month <- toupper(C2M(substr(x,1,1)))
             year <- as.numeric(substr(x,2,3)) + 2000

Modified: pkg/FinancialInstrument/R/synthetic.R
===================================================================
--- pkg/FinancialInstrument/R/synthetic.R	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/R/synthetic.R	2011-09-05 04:31:48 UTC (rev 749)
@@ -13,9 +13,11 @@
 
 #' @export
 #' @rdname synthetic.instrument
-synthetic <- function(primary_id , currency , multiplier=1, identifiers = NULL, ..., members=NULL, type="synthetic")
+synthetic <- function(primary_id=NULL, currency=NULL, multiplier=1, identifiers = NULL, ..., members=NULL, type="synthetic")
 {
-    instrument(primary_id=primary_id , currency=currency , multiplier=multiplier , identifiers = identifiers, ...=..., type=type, members=members, assign_i=TRUE )    
+    if (missing(primary_id) || (is.null(primary_id))) primary_id <- make_spread_id(members)
+    if (missing(currency) || (is.null(currency))) currency <- getInstrument(members[[1]])$currency
+    instrument(primary_id=primary_id , currency=currency , multiplier=multiplier , identifiers = identifiers, ...=..., type=type, members=members, assign_i=TRUE )
 }
 
 #' constructors for synthetic instruments
@@ -95,7 +97,10 @@
 #' be a string describing the \code{members}. 
 #' It will be \code{\link{strsplit}} using the regex "[-;:_,\\.]" to create the \code{members} vector,
 #' and potentially combined with a \code{root_id}.
-#' 
+#'
+#' The wrappers will build \code{primary_id} if is NULL, either by combining \code{root_id} and \code{suffix_id}, or
+#' by passing \code{members} in a call to \code{\link{make_spread_id}}
+#'
 #' We welcome assistance from others to model more complex OTC derivatives such as swap products.
 #'
 #' @aliases synthetic.instrument synthetic spread guaranteed_spread butterfly
@@ -125,35 +130,49 @@
     identifiers = NULL, type = c("synthetic.instrument", "synthetic")) 
 {
     if (!is.list(members)) {
-        if (length(members) != length(memberratio) | length(members) < 
-            2) {
+        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)
-        }
+        memberlist <- list(members = members, memberratio = memberratio, 
+                            currencies = vector(), memberpositions = NULL)
         for (member in members) {
-            tmp_symbol <- member
             tmp_instr <- try(getInstrument(member, silent=TRUE))
-            if (inherits(tmp_instr, "try-error") | !is.instrument(tmp_instr)) {
-                message(paste("Instrument", tmp_symbol, " not found, using currency of", 
-                  currency))
+            if (inherits(tmp_instr, "try-error") | !is.instrument(tmp_instr)) {                
+                cat(paste("Instrument ", member, " not found, ",sep=""))
+                if(missing(currency) || is.null(currency)) {
+                    stop("'currency' must be provided if member instruments are not defined") 
+                } else cat("using currency of", currency, "\n")
                 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 (all(do.call(c, lapply(members, is.instrument)))) { #if members is a list of instruments
+            instrlist <- members
+            members <- do.call(c, lapply(instrlist, FUN=function(x) x$primary_id))
+            memberlist <- list(members = members, memberratio = memberratio, 
+                            currencies = vector(), memberpositions = NULL)
+            for (i in 1:length(members)) {
+                tmp_instr <- instrlist[[i]]
+                memberlist$currencies[members[i]] <- tmp_instr$currency
+            }
+        } else {
+            memberlist = members
+            members <- memberlist$members
+        }    
     }
-    if (is.null(currency)) 
+
+    names(memberlist$members) <- memberlist$members
+    names(memberlist$memberratio) <- memberlist$members
+    names(memberlist$currencies) <- memberlist$members
+
+    if (missing(primary_id) || is.null(primary_id)) 
+        primary_id <- make_spread_id(members)
+    if (missing(currency) || is.null(currency)) 
         currency <- as.character(memberlist$currencies[1])
 	
     synthetic(primary_id = primary_id, currency = currency, multiplier = multiplier, 
@@ -164,7 +183,7 @@
 
 #' @export
 #' @rdname synthetic.instrument
-spread <- function (primary_id, currency = NULL, members, memberratio, tick_size=NULL,
+spread <- function (primary_id = NULL, currency = NULL, members, memberratio, tick_size=NULL,
     ..., multiplier = 1, identifiers = NULL) 
 {
     synthetic.instrument(primary_id = primary_id, currency = currency, 
@@ -176,7 +195,7 @@
 
 #' @export
 #' @rdname synthetic.instrument
-butterfly <- function(primary_id, currency=NULL, members,tick_size=NULL, identifiers=NULL, ...)
+butterfly <- function(primary_id = NULL, currency=NULL, members,tick_size=NULL, identifiers=NULL, ...)
 {
 ##TODO: butterfly can refer to expirations (futures) or strikes (options)
 ##TODO: A butterfly could either have 3 members that are outrights, or 2 members that are spreads
@@ -195,7 +214,7 @@
 
 #' @export
 #' @rdname synthetic.instrument
-guaranteed_spread <- calendar_spread <- function (primary_id, currency=NULL, root_id=NULL, suffix_id=NULL, members = NULL, memberratio = c(1,-1), ..., 
+guaranteed_spread <- calendar_spread <- function (primary_id=NULL, currency=NULL, root_id=NULL, suffix_id=NULL, members = NULL, memberratio = c(1,-1), ..., 
     multiplier = NULL, identifiers = NULL, tick_size=NULL)
 {
 
@@ -206,28 +225,39 @@
 			id <- paste(primary_id, suffix_id, sep = "_")
 		}
     } else id <- primary_id
-    
+
+    if (is.null(id) && !is.null(members)) id <- make_spread_id(members, root=root_id)
+
     id<-make.names(id) #force syntactically valid primary_id
-    
-	if (is.null(members) && hasArg(suffix_id)) {
+
+    if (is.null(suffix_id)) suffix_id <- parse_id(id)$suffix
+    if (is.null(root_id)) root_id <- parse_id(id)$root
+
+	if (is.null(members)) {
 		#construct members from suffix_id and either primary_id or root_id
-        members <- unlist(strsplit(suffix_id, "[-;:_,\\.]"))
-		if(hasArg(root_id)) {
-			members <- paste(root_id,members, sep ="_")
-		} else {
-			members <- paste(primary_id, members, sep = "_")
-		}		
+		members <- unlist(strsplit(suffix_id, "[-;:_,\\.]"))
+		members <- paste(root_id,members, sep ="_")
 	}
 	
-	if(hasArg(root_id)) {
-		# go get other instrument quantities from the root contract
-		root_contract<-getInstrument(root_id)
-		if(is.instrument(root_contract)){
-			if(is.null(currency)) currency <- root_contract$currency
-			if(is.null(multiplier)) multiplier <- root_contract$multiplier
-			if(is.null(tick_size)) tick_size <-  root_contract$tick_size
-		}
-	} 
+	# go get other instrument quantities from the root contract
+	root_contract<-try(getInstrument(root_id,silent=TRUE))
+    if (!is.instrument(root_contract)) root_contract <- try(getRoot(root_id,'future'),silent=TRUE)
+    if (!is.instrument(root_contract)) root_contract <- try(getRoot(root_id,'option'),silent=TRUE)
+	if(is.instrument(root_contract)){
+		if(is.null(currency)) currency <- root_contract$currency
+		if(is.null(multiplier)) multiplier <- root_contract$multiplier
+		if(is.null(tick_size)) tick_size <-  root_contract$tick_size
+	} else {
+        if (is.null(multiplier)) {
+            message(paste(root_id, 'is not defined, using multiplier of 1'))
+            multiplier <- 1
+        }
+        if (is.null(currency)) {
+            m1 <- getInstrument(members[[1]],silent=TRUE)
+            if (is.instrument(m1))
+                currency <- m1$currency
+        }
+    }
 	
     synthetic.instrument(primary_id = id, currency = currency, members = members, 
 	memberratio = memberratio, multiplier = multiplier, identifiers = NULL, 

Added: pkg/FinancialInstrument/man/getRoot.Rd
===================================================================
--- pkg/FinancialInstrument/man/getRoot.Rd	                        (rev 0)
+++ pkg/FinancialInstrument/man/getRoot.Rd	2011-09-05 04:31:48 UTC (rev 749)
@@ -0,0 +1,58 @@
+\name{getRoot}
+\alias{get_future}
+\alias{get_option}
+\alias{getRoot}
+\title{Get the root contract specs for an instrument}
+\usage{
+  getRoot(root_id, type = c("future", "option"))
+
+  get_option(root_id)
+
+  get_future(root_id)
+}
+\arguments{
+  \item{root_id}{string (e.g. "ES", ".ES", or "..ES" for
+  e-mini S&P 500 futures)}
+
+  \item{type}{character. type of instrument to look for
+  ("future" or "option"). Alternatively, can be numeric: 1
+  for "future" or 2 for "option"}
+}
+\value{
+  an object of class \code{type}
+}
+\description{
+  Get a \code{future} or \code{option} object
+}
+\details{
+  \code{get_option} and \code{get_future} are wrappers, and
+  they are called internally by \code{\link{future_series}}
+  and \code{\link{option_series}}
+
+  \code{\link{future}} and \code{\link{option}} objects may
+  have a primary_id that begins with 1 or 2 dots (in order
+  to avoid naming conflics).  For example, the root specs
+  for options (or futures) on the stock with ticker "SPY"
+  may be stored with a primary_id of "SPY", ".SPY", or
+  "..SPY"
+
+  This function will try calling
+  \code{\link{getInstrument}} using each possible
+  primary_id until it finds the instrument that is of
+  appropriate \code{type}.
+}
+\examples{
+\dontrun{
+option('.SPY',currency("USD"),100,underlying_id=stock("SPY","USD"))
+future("..SPY","USD", 100, underlying_id="SPY")
+getRoot("SPY", 'future')
+getRoot("SPY", 'option')
+}
+}
+\author{
+  Garrett See
+}
+\seealso{
+  \code{\link{getInstrument}}
+}
+

Modified: pkg/FinancialInstrument/man/synthetic.instrument.Rd
===================================================================
--- pkg/FinancialInstrument/man/synthetic.instrument.Rd	2011-09-01 11:25:16 UTC (rev 748)
+++ pkg/FinancialInstrument/man/synthetic.instrument.Rd	2011-09-05 04:31:48 UTC (rev 749)
@@ -6,8 +6,8 @@
 \alias{synthetic.instrument}
 \title{synthetic instrument constructors}
 \usage{
-  synthetic(primary_id, currency, multiplier = 1,
-  identifiers = NULL, ..., members = NULL, type =
+  synthetic(primary_id = NULL, currency = NULL, multiplier
+  = 1, identifiers = NULL, ..., members = NULL, type =
   "synthetic")
 
   synthetic.instrument(primary_id, currency, members,
@@ -15,17 +15,17 @@
   identifiers = NULL, type = c("synthetic.instrument",
   "synthetic"))
 
-  spread(primary_id, currency = NULL, members, memberratio,
-  tick_size = NULL, ..., multiplier = 1, identifiers =
-  NULL)
+  spread(primary_id = NULL, currency = NULL, members,
+  memberratio, tick_size = NULL, ..., multiplier = 1,
+  identifiers = NULL)
 
-  butterfly(primary_id, currency = NULL, members, tick_size
-  = NULL, identifiers = NULL, ...)
+  butterfly(primary_id = NULL, currency = NULL, members,
+  tick_size = NULL, identifiers = NULL, ...)
 
-  guaranteed_spread(primary_id, currency = NULL, root_id =
-  NULL, suffix_id = NULL, members = NULL, memberratio =
-  c(1, -1), ..., multiplier = NULL, identifiers = NULL,
-  tick_size = NULL)
+  guaranteed_spread(primary_id = NULL, currency = NULL,
+  root_id = NULL, suffix_id = NULL, members = NULL,
+  memberratio = c(1, -1), ..., multiplier = NULL,
+  identifiers = NULL, tick_size = NULL)
 }
 \arguments{
   \item{primary_id}{chr string of primary identifier of
@@ -93,6 +93,11 @@
   create the \code{members} vector, and potentially
   combined with a \code{root_id}.
 
+  The wrappers will build \code{primary_id} if is NULL,
+  either by combining \code{root_id} and \code{suffix_id},
+  or by passing \code{members} in a call to
+  \code{\link{make_spread_id}}
+
   We welcome assistance from others to model more complex
   OTC derivatives such as swap products.
 }



More information about the Blotter-commits mailing list