[Blotter-commits] r1231 - in pkg/quantstrat: . R demo man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Oct 26 23:07:53 CEST 2012


Author: opentrades
Date: 2012-10-26 23:07:53 +0200 (Fri, 26 Oct 2012)
New Revision: 1231

Modified:
   pkg/quantstrat/NAMESPACE
   pkg/quantstrat/R/osFUNs.R
   pkg/quantstrat/R/paramsets.R
   pkg/quantstrat/R/strategy.R
   pkg/quantstrat/R/utils.R
   pkg/quantstrat/demo/luxor.StopLoss.R
   pkg/quantstrat/demo/luxor.StopTrailing.R
   pkg/quantstrat/demo/luxor.TakeProfit.R
   pkg/quantstrat/demo/luxor.exits.R
   pkg/quantstrat/demo/luxor.orderchains.R
   pkg/quantstrat/man/add.constraint.Rd
   pkg/quantstrat/man/add.distribution.Rd
   pkg/quantstrat/man/apply.paramset.Rd
   pkg/quantstrat/man/delete.paramset.Rd
Log:
- various improvements in paramsets.R
- load.strategy() and save.strategy()
- stop() if isMaxPos() called but PosLimit==NULL
- luxor.exists.R creates and stores luxor.RData strategy object in file
- luxor.{StopLoss,StopTrailing,TakeProfit}.R now using stored strategy luxor.RData
- some more documentation



Modified: pkg/quantstrat/NAMESPACE
===================================================================
--- pkg/quantstrat/NAMESPACE	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/NAMESPACE	2012-10-26 21:07:53 UTC (rev 1231)
@@ -22,12 +22,14 @@
 export(initOrders)
 export(initStrategy)
 export(is.strategy)
+export(load.strategy)
 export(match.names)
 export(osMaxPos)
 export(osNoOp)
 export(rm.strat)
 export(ruleOrderProc)
 export(ruleSignal)
+export(save.strategy)
 export(setParameterConstraint)
 export(setParameterDistribution)
 export(sigComparison)
@@ -35,6 +37,7 @@
 export(sigFormula)
 export(sigPeak)
 export(sigThreshold)
+export(store.strategy)
 export(strategy)
 export(tradeGraphs)
 export(updateOrders)

Modified: pkg/quantstrat/R/osFUNs.R
===================================================================
--- pkg/quantstrat/R/osFUNs.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/R/osFUNs.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -108,6 +108,8 @@
     pos<-getPosQty(portfolio,symbol,timestamp)
     # check against max position
     PosLimit<-getPosLimit(portfolio,symbol,timestamp)
+    if(is.null(PosLimit))
+        stop(paste('no position limit defined for portfolio', portfolio))
 	
 	#TODO add handling for orderqty='all', and handle risk ruletype separately
 	

Modified: pkg/quantstrat/R/paramsets.R
===================================================================
--- pkg/quantstrat/R/paramsets.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/R/paramsets.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -13,7 +13,7 @@
 #
 # Authors: Yu Chen, Jan Humme
 #
-# This code is a new implementation of earlier work by Yu Chen
+# This code is a based on earlier work by Yu Chen
 #
 ###############################################################################
 #
@@ -36,6 +36,8 @@
 #
 ###############################################################################
 
+# creates a copy of a portfolio, stripping all history (transactions etc)
+
 clone.portfolio <- function(portfolio.st, cloned.portfolio.st, strip.history=TRUE)
 {
     #must.have.args(match.call(), c('portfolio.st', 'cloned.portfolio.st'))
@@ -59,6 +61,8 @@
     return(cloned.portfolio.st)
 }
 
+# creates a copy of an orderbook, stripping all orders
+
 clone.orderbook <- function(portfolio.st, cloned.portfolio.st, strip.history=TRUE)
 {
     #must.have.args(match.call(), c('portfolio.st', 'cloned.portfolio.st'))
@@ -77,16 +81,14 @@
     assign(paste("order_book", cloned.portfolio.st, sep='.'), order.book, envir=.strategy)
 }
 
-################################################################################
+### local functions ############################################################
 
 must.be.paramset <- function(strategy, paramset)
 {
     if(!(paramset %in% names(strategy$paramsets)))
-        stop(paste(paramset, ': not a known paramset in strategy', strategy$name))
+        stop(paste(paramset, ': not a paramset in strategy', strategy$name))
 }
 
-### local functions ############################################################
-
 create.paramset <- function(strategy, paramset.label)
 {
     strategy$paramsets[[paramset.label]] <- list()
@@ -96,12 +98,6 @@
     strategy
 }
 
-may.create.paramset <- function(strategy, paramset.label)
-{
-    if(!(paramset.label %in% names(strategy$paramsets)))
-        create.paramset(strategy, paramset.label)
-}
-
 expand.distributions <- function(distributions)
 {
     param.values <- list()
@@ -192,37 +188,61 @@
 
 #' Delete a paramset from a strategy
 #' 
-#' @param strategy: the name of the strategy object
-#' @param paramset.label: a label uniquely identifying the paramset within the strategy
+#' Delete a paramset from a strategy, including its distributions and constraints.
+#' 
+#' @param strategy the name of the strategy object
+#' @param paramset.label a label uniquely identifying the paramset within the strategy
 #'
 #' @author Jan Humme
 #' @export
+#' @seealso \code{\link{add.constraint}}, \code{\link{add.constraint}}, \code{\link{apply.paramset}}
 
-delete.paramset <- function(strategy, paramset.label)
+delete.paramset <- function(strategy, paramset.label, store=TRUE)
 {
     must.have.args(match.call(), c('strategy', 'paramset.label'))
 
+    if(!is.strategy(strategy))
+    {
+        strategy <- must.be.strategy(strategy)
+        store <- TRUE
+    }
+
     if(!is.null(strategy$paramsets[[paramset.label]]))
         strategy$paramsets[[paramset.label]] <- NULL
+
+    if(store)
+    {
+        store.strategy(strategy)
+        return(strategy$name)
+    }
+    return(strategy)
 }
 
 #' Adds a distribution to a paramset in a strategy
 #' 
-#' @param strategy: the name of the strategy object
-#' @param paramset.label: a label uniquely identifying the paramset within the strategy
-#' @param component.type: one of c('indicator', 'signal', 'order', 'enter', 'exit', chain')
-#' @param component.label: a label identifying the component. must be unique per component type
-#' @param variable: the name of the variable in the component
-#' @param label: a label uniquely identifying the distribution within the paramset
+#' Creates a distribution in paramset, where a distribution consists of the name of a variable in
+#' a strategy component plus a range of values for this variable.
+#' 
+#' @param strategy the name of the strategy object to add the distribution to
+#' @param paramset.label a label uniquely identifying the paramset within the strategy
+#' @param component.type one of c('indicator', 'signal', 'order', 'enter', 'exit', 'chain')
+#' @param component.label a label identifying the component. must be unique per component type
+#' @param variable the name of the variable in the component
+#' @param label a label uniquely identifying the distribution within the paramset
 #'
 #' @author Jan Humme
 #' @export
+#' @seealso \code{\link{add.constraint}}, \code{\link{delete.paramset}}, \code{\link{apply.paramset}}
 
-add.distribution <- function(strategy, paramset.label, component.type, component.label, variable, weight=NULL, label)
+add.distribution <- function(strategy, paramset.label, component.type, component.label, variable, weight=NULL, label, store=TRUE)
 {
     must.have.args(match.call(), c('strategy', 'paramset.label', 'component.type', 'component.label', 'variable', 'label'))
 
-    must.be.strategy(strategy)
+    if(!is.strategy(strategy))
+    {
+        strategy <- must.be.strategy(strategy)
+        store <- TRUE
+    }
 
     new_distribution <- list()
     new_distribution$component.type <- component.type
@@ -230,52 +250,81 @@
     new_distribution$variable <- variable
     new_distribution$weight <- weight
 
-    may.create.paramset(strategy, paramset.label)
+    if(!(paramset.label %in% names(strategy$paramsets)))
+        strategy <- create.paramset(strategy, paramset.label)
 
     strategy$paramsets[[paramset.label]]$distributions[[label]] <- new_distribution
 
-    strategy
+    if(store)
+    {
+        store.strategy(strategy)
+        return(strategy$name)
+    }
+    return(strategy)
 }
 
-#' Adds a constraint to 2 distributions within a paramset
+#' Adds a constraint on 2 distributions within a paramset
 #' 
-#' @param strategy: the name of the strategy object
-#' @param paramset.label: a label uniquely identifying the paramset within the strategy
-#' @param distribution.label.1: a label identifying the first distribution
-#' @param distribution.label.2: a label identifying the second distribution
-#' @param operator: an operator specifying the relational constraint between the 2 distributions
-#' @param label: a label uniquely identifying the constraint within the paramset
+#' Creates a constraint on 2 distributions in a paramset, i.e. a restriction limiting the allowed
+#' combinations from the ranges for distribution 1 and distribution 2.
+#' 
+#' @param strategy the name of the strategy object to add the constraint to
+#' @param paramset.label a label uniquely identifying the paramset within the strategy
+#' @param distribution.label.1 a label identifying the first distribution
+#' @param distribution.label.2 a label identifying the second distribution
+#' @param operator an operator specifying the relational constraint between the 2 distributions
+#' @param label a label uniquely identifying the constraint within the paramset
 #'
 #' @author Jan Humme
 #' @export
+#' @seealso \code{\link{add.distribution}}, \code{\link{delete.paramset}}, \code{\link{apply.paramset}}
 
-add.constraint <- function(strategy, paramset.label, distribution.label.1, distribution.label.2, operator, label)
+add.constraint <- function(strategy, paramset.label, distribution.label.1, distribution.label.2, operator, label, store=TRUE)
 {
     must.have.args(match.call(), c('strategy', 'paramset.label', 'distribution.label.1', 'distribution.label.2', 'operator', 'label'))
 
-    must.be.strategy(strategy)
+    if(!is.strategy(strategy))
+    {
+        strategy <- must.be.strategy(strategy)
+        store <- TRUE
+    }
 
     new_constraint <- list()
     new_constraint$distributions <- list(distribution.label.1, distribution.label.2)
     new_constraint$operator <- operator
 
-    may.create.paramset(strategy, paramset.label)
+    if(!(paramset.label %in% names(strategy$paramsets)))
+        strategy <- create.paramset(strategy, paramset.label)
 
     strategy$paramsets[[paramset.label]]$constraints[[label]] <- new_constraint
 
-    strategy
+    if(store)
+    {
+        store.strategy(strategy)
+        return(strategy$name)
+    }
+    return(strategy)
 }
 
 #' Apply a paramset to the strategy
+#'
+#' This function will run applyStrategy() on portfolio.st, once for each parameter combination as specified by
+#' the parameter distributions and constraints in the paramset. Results are gathered and returned as a list
+#' containing a slot for each parameter combination.
+#'
+#' apply.paramset uses the foreach package to start the runs for each parameter combination, and as such allows
+#' for parallel processing. It is up to the caller to load and register an appropriate backend, eg. doMC,
+#' doParallel or doRedis.
 #' 
-#' @param strategy: the name of the strategy object
-#' @param paramset.label: a label uniquely identifying the paramset within the strategy
-#' @param portfolio.st: a string variable
-#' @param nsamples: if > 0 then take a sample of only size nsamples from the paramset
-#' @param verbose
+#' @param strategy the name of the strategy object
+#' @param paramset.label a label uniquely identifying the paramset within the strategy
+#' @param portfolio.st a string variable
+#' @param nsamples if > 0 then take a sample of only size nsamples from the paramset
+#' @param verbose return full information, in particular the .blotter environment, default FALSE
 #'
 #' @author Jan Humme
 #' @export
+#' @seealso \code{\link{add.constraint}}, \code{\link{add.constraint}}, \code{\link{delete.paramset}}
 
 apply.paramset <- function(strategy, paramset.label, portfolio.st, nsamples=0, verbose=FALSE)
 {
@@ -284,7 +333,7 @@
 
     must.have.args(match.call(), c('strategy', 'paramset.label', 'portfolio.st'))
 
-    must.be.strategy(strategy)
+    strategy <- must.be.strategy(strategy)
     must.be.paramset(strategy, paramset.label)
 
     portfolio <- getPortfolio(portfolio.st)
@@ -311,16 +360,16 @@
     {
         if(verbose) print(param.combo)
 
-        # loops must be run with an empty .blotter environment each, or .blotter appears to accumulate 
-        # all portfolios and accounts, passing them from one loop to the next on each CPU - JH July 2012
+        # environment data accumulate with each transition through the foreach loop, so must be cleaned
         rm(list=ls(pos=.blotter), pos=.blotter)
         rm(list=ls(pos=.strategy), pos=.strategy)
         rm(list=ls(pos=FinancialInstrument:::.instrument), pos=FinancialInstrument:::.instrument)
 
         gc(verbose=verbose)
 
-        .getSymbols<-as.environment(symbol.list)
-        for(symbol in symbol.names) { assign(symbol, eval(as.name(symbol)), .GlobalEnv) }
+        .getSymbols <- as.environment(symbol.list)
+        for(symbol in symbol.names)
+            assign(symbol, eval(as.name(symbol)), .GlobalEnv)
 
         list2env(env.blotter, envir=.blotter)
         list2env(env.instrument, envir=FinancialInstrument:::.instrument)

Modified: pkg/quantstrat/R/strategy.R
===================================================================
--- pkg/quantstrat/R/strategy.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/R/strategy.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -191,6 +191,32 @@
         .strategy <<- new.env()
 }
 
+#' @export
+store.strategy <- function(strategy)
+{
+    assign(strategy$name, strategy, envir=as.environment(.strategy))
+}
+
+# load a strategy object from disk into memory
+#' @export
+load.strategy <- function(strategy.name)
+{
+    file.name <- paste(strategy.name, 'RData', sep='.')
+
+    load(file=file.name, envir=.strategy)
+    assign(.strategy$strategy$name, .strategy$strategy, envir=.strategy)
+}
+
+# save a strategy object from memory onto disk
+#' @export
+save.strategy <- function(strategy.name)
+{
+    strategy <- get(as.character(strategy.name), pos=.strategy, inherits=TRUE)
+    file.name <- paste(strategy.name, 'RData', sep='.')
+
+    save(strategy, pos=.strategy, file=file.name)
+}
+
 ###############################################################################
 # R (http://r-project.org/) Quantitative Strategy Model Framework
 #

Modified: pkg/quantstrat/R/utils.R
===================================================================
--- pkg/quantstrat/R/utils.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/R/utils.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -26,12 +26,23 @@
 must.be.strategy <- function(strategy)
 {
     if(!is.strategy(strategy))
-        stop(paste(strategy, ': not a strategy'))
+    {
+        strategy<-try(getStrategy(strategy))
+
+        if(inherits(strategy,"try-error"))
+            stop(paste(strategy, ': not a strategy'))
+    }
+    return(strategy)
 }
 
 must.be.portfolio <- function(portfolio)
 {
     if(!is.portfolio(portfolio))
-        stop(paste(portfolio, ': not a portfolio'))
+    {
+        portfolio<-try(getPortfolio(portfolio))
+
+        if(inherits(portfolio,"try-error"))
+            stop(paste(portfolio, ': not a portfolio'))
+    }
 }
 

Modified: pkg/quantstrat/demo/luxor.StopLoss.R
===================================================================
--- pkg/quantstrat/demo/luxor.StopLoss.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/demo/luxor.StopLoss.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -1,6 +1,69 @@
+#!/usr/bin/Rscript --vanilla
+#
+# Jan Humme (@opentrades) - August 2012
+#
+# Tested and found to work correctly using blotter r1230
+#
+# From Jaekle & Tamasini: A new approach to system development and portfolio optimisation (ISBN 978-1-905641-79-6)
+#
+# compute StopLoss percentage for various paramsets
 
-source('luxor.exits.R')
+require(quantstrat)
 
+options(width = 240)
+#Sys.setenv(TZ="GMT")
+
+.qty=100000
+
+.fast = 10
+.slow = 30
+
+.qty=100000
+.th=0.0005
+.txn=0
+
+initDate = '2002-10-21'
+.from='2002-10-21'
+#.to='2008-07-04'
+#.to='2003-12-31'
+.to='2002-10-31'
+
+###
+
+currency(c('GBP', 'USD'))
+
+exchange_rate(c('GBPUSD'), tick_size=0.0001)
+
+###
+
+setSymbolLookup.FI('~/R.symbols/', 'GBPUSD')
+#setSymbolLookup.FI('../data/', 'GBPUSD')
+
+getSymbols('GBPUSD', from=.from, to=.to, verbose=FALSE)
+GBPUSD = to.minutes30(GBPUSD)
+GBPUSD = align.time(to.minutes30(GBPUSD), 1800)
+
+###
+
+strategy.st = 'luxor'
+portfolio.st = 'forex'
+account.st = 'IB1'
+
+initPortf(portfolio.st, symbols='GBPUSD', initDate=initDate, currency='USD')
+addPosLimit(
+            portfolio=portfolio.st,
+            symbol='GBPUSD',
+            timestamp=initDate,
+            maxpos=.qty)
+
+initAcct(account.st, portfolios=portfolio.st, initDate=initDate, currency='USD')
+
+###
+
+initOrders(portfolio.st, initDate=initDate)
+
+load.strategy(strategy.st)
+
 ############################
 
 require(foreach)
@@ -18,6 +81,6 @@
 
 ############################
 
-results <- apply.paramset(s, paramset.label='StopLoss', portfolio.st=p, verbose=TRUE)
+results <- apply.paramset(strategy.st, paramset.label='StopLoss', portfolio.st=portfolio.st, verbose=TRUE)
 
 print(results$tradeStats)

Modified: pkg/quantstrat/demo/luxor.StopTrailing.R
===================================================================
--- pkg/quantstrat/demo/luxor.StopTrailing.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/demo/luxor.StopTrailing.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -1,6 +1,69 @@
+#!/usr/bin/Rscript --vanilla
+#
+# Jan Humme (@opentrades) - August 2012
+#
+# Tested and found to work correctly using blotter r1230
+#
+# From Jaekle & Tamasini: A new approach to system development and portfolio optimisation (ISBN 978-1-905641-79-6)
+#
+# compute StopTrailing percentage for various paramsets
 
-source('luxor.exits.R')
+require(quantstrat)
 
+options(width = 240)
+#Sys.setenv(TZ="GMT")
+
+.qty=100000
+
+.fast = 10
+.slow = 30
+
+.qty=100000
+.th=0.0005
+.txn=0
+
+initDate = '2002-10-21'
+.from='2002-10-21'
+#.to='2008-07-04'
+#.to='2003-12-31'
+.to='2002-10-31'
+
+###
+
+currency(c('GBP', 'USD'))
+
+exchange_rate(c('GBPUSD'), tick_size=0.0001)
+
+###
+
+setSymbolLookup.FI('~/R.symbols/', 'GBPUSD')
+#setSymbolLookup.FI('../data/', 'GBPUSD')
+
+getSymbols('GBPUSD', from=.from, to=.to, verbose=FALSE)
+GBPUSD = to.minutes30(GBPUSD)
+GBPUSD = align.time(to.minutes30(GBPUSD), 1800)
+
+###
+
+strategy.st = 'luxor'
+portfolio.st = 'forex'
+account.st = 'IB1'
+
+initPortf(portfolio.st, symbols='GBPUSD', initDate=initDate, currency='USD')
+addPosLimit(
+            portfolio=portfolio.st,
+            symbol='GBPUSD',
+            timestamp=initDate,
+            maxpos=.qty)
+
+initAcct(account.st, portfolios=portfolio.st, initDate=initDate, currency='USD')
+
+###
+
+initOrders(portfolio.st, initDate=initDate)
+
+load.strategy(strategy.st)
+
 ############################
 
 require(foreach)
@@ -18,6 +81,6 @@
 
 ############################
 
-results <- apply.paramset(s, paramset.label='StopTrailing', portfolio.st=p, verbose=TRUE)
+results <- apply.paramset(strategy.st, paramset.label='StopTrailing', portfolio.st=portfolio.st, verbose=TRUE)
 
 print(results$tradeStats)

Modified: pkg/quantstrat/demo/luxor.TakeProfit.R
===================================================================
--- pkg/quantstrat/demo/luxor.TakeProfit.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/demo/luxor.TakeProfit.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -1,6 +1,69 @@
+#!/usr/bin/Rscript --vanilla
+#
+# Jan Humme (@opentrades) - August 2012
+#
+# Tested and found to work correctly using blotter r1230
+#
+# From Jaekle & Tamasini: A new approach to system development and portfolio optimisation (ISBN 978-1-905641-79-6)
+#
+# compute TakeProfit percentage for various paramsets
 
-source('luxor.exits.R')
+require(quantstrat)
 
+options(width = 240)
+#Sys.setenv(TZ="GMT")
+
+.qty=100000
+
+.fast = 10
+.slow = 30
+
+.qty=100000
+.th=0.0005
+.txn=0
+
+initDate = '2002-10-21'
+.from='2002-10-21'
+#.to='2008-07-04'
+#.to='2003-12-31'
+.to='2002-10-31'
+
+###
+
+currency(c('GBP', 'USD'))
+
+exchange_rate(c('GBPUSD'), tick_size=0.0001)
+
+###
+
+setSymbolLookup.FI('~/R.symbols/', 'GBPUSD')
+#setSymbolLookup.FI('../data/', 'GBPUSD')
+
+getSymbols('GBPUSD', from=.from, to=.to, verbose=FALSE)
+GBPUSD = to.minutes30(GBPUSD)
+GBPUSD = align.time(to.minutes30(GBPUSD), 1800)
+
+###
+
+strategy.st = 'luxor'
+portfolio.st = 'forex'
+account.st = 'IB1'
+
+initPortf(portfolio.st, symbols='GBPUSD', initDate=initDate, currency='USD')
+addPosLimit(
+            portfolio=portfolio.st,
+            symbol='GBPUSD',
+            timestamp=initDate,
+            maxpos=.qty)
+
+initAcct(account.st, portfolios=portfolio.st, initDate=initDate, currency='USD')
+
+###
+
+initOrders(portfolio.st, initDate=initDate)
+
+load.strategy(strategy.st)
+
 ############################
 
 require(foreach)
@@ -18,6 +81,6 @@
 
 ############################
 
-results <- apply.paramset(s, paramset.label='TakeProfit', portfolio.st=p, verbose=TRUE)
+results <- apply.paramset(strategy.st, paramset.label='TakeProfit', portfolio.st=portfolio.st, verbose=TRUE)
 
 print(results$tradeStats)

Modified: pkg/quantstrat/demo/luxor.exits.R
===================================================================
--- pkg/quantstrat/demo/luxor.exits.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/demo/luxor.exits.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -1,23 +1,22 @@
 #!/usr/bin/Rscript --vanilla
 
+require(quantstrat)
+
+source('luxor.basic.R')
+
 .FastSMA = (1:20)
 .SlowSMA = (30:80)
 
 .StopLoss = seq(0.1, 2.0, length.out=20)/100
-
 .StopTrailing = seq(0.1, 2.0, length.out=20)/100
-
 .TakeProfit = seq(0.1, 2.0, length.out=20)/100
 
-#require(quantstrat)
+#s<-getStrategy('luxor')
+s <- 'luxor'
 
-source('luxor.orderchains.R')
-
-s<-getStrategy('luxor')
-
 ### SMA paramset
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'SMA',
 	component.type = 'indicator',
 	component.label = 'nFast',
@@ -25,7 +24,7 @@
 	label = 'nFAST'
 )
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'SMA',
 	component.type = 'indicator',
 	component.label = 'nSlow',
@@ -33,7 +32,7 @@
 	label = 'nSLOW'
 )
 
-s<-add.constraint(s,
+add.constraint(s,
 	paramset.label = 'SMA',
 	distribution.label.1 = 'nFAST',
 	distribution.label.2 = 'nSLOW',
@@ -43,7 +42,7 @@
 
 ### Stop Loss paramset
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'StopLoss',
 	component.type = 'chain',
 	component.label = 'StopLossLONG',
@@ -51,7 +50,7 @@
 	label = 'StopLossLONG'
 )
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'StopLoss',
 	component.type = 'chain',
 	component.label = 'StopLossSHORT',
@@ -59,7 +58,7 @@
 	label = 'StopLossSHORT'
 )
 
-s<-add.constraint(s,
+add.constraint(s,
 	paramset.label = 'StopLoss',
 	distribution.label.1 = 'StopLossLONG',
 	distribution.label.2 = 'StopLossSHORT',
@@ -69,7 +68,7 @@
 
 ### Stop Trailing paramset
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'StopTrailing',
 	component.type = 'chain',
 	component.label = 'StopTrailingLONG',
@@ -77,7 +76,7 @@
 	label = 'StopTrailingLONG'
 )
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'StopTrailing',
 	component.type = 'chain',
 	component.label = 'StopTrailingSHORT',
@@ -85,7 +84,7 @@
 	label = 'StopTrailingSHORT'
 )
 
-s<-add.constraint(s,
+add.constraint(s,
 	paramset.label = 'StopTrailing',
 	distribution.label.1 = 'StopTrailingLONG',
 	distribution.label.2 = 'StopTrailingSHORT',
@@ -95,7 +94,7 @@
 
 ### Take Profit paramset
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'TakeProfit',
 	component.type = 'chain',
 	component.label = 'TakeProfitLONG',
@@ -103,7 +102,7 @@
 	label = 'TakeProfitLONG'
 )
 
-s<-add.distribution(s,
+add.distribution(s,
 	paramset.label = 'TakeProfit',
 	component.type = 'chain',
 	component.label = 'TakeProfitSHORT',
@@ -111,7 +110,7 @@
 	label = 'TakeProfitSHORT'
 )
 
-s<-add.constraint(s,
+add.constraint(s,
 	paramset.label = 'TakeProfit',
 	distribution.label.1 = 'TakeProfitLONG',
 	distribution.label.2 = 'TakeProfitSHORT',
@@ -119,3 +118,6 @@
 	label = 'TakeProfit'
 )
 
+###
+
+save.strategy('luxor')

Modified: pkg/quantstrat/demo/luxor.orderchains.R
===================================================================
--- pkg/quantstrat/demo/luxor.orderchains.R	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/demo/luxor.orderchains.R	2012-10-26 21:07:53 UTC (rev 1231)
@@ -2,7 +2,7 @@
 #
 # Jan Humme (@opentrades) - August 2012
 #
-# Tested and found to work correctly using blotter r1123
+# Tested and found to work correctly using blotter r1230
 #
 # From Jaekle & Tamasini: A new approach to system development and portfolio optimisation (ISBN 978-1-905641-79-6)
 #
@@ -129,7 +129,8 @@
 	),
 	type='chain',
 	parent='EnterLONG',
-	label='StopLossLONG'
+	label='StopLossLONG',
+	storefun=FALSE
 )
 
 add.rule(s, name = 'ruleSignal',
@@ -145,7 +146,8 @@
 	),
 	type='chain',
 	parent='EnterSHORT',
-	label='StopLossSHORT'
+	label='StopLossSHORT',
+	storefun=FALSE
 )
 
 ### stop-trailing
@@ -165,7 +167,8 @@
 	),
 	type='chain',
 	parent='EnterLONG',
-	label='StopTrailingLONG'
+	label='StopTrailingLONG',
+	storefun=FALSE
 )
 
 add.rule(s, name = 'ruleSignal',
@@ -181,7 +184,8 @@
 	),
 	type='chain',
 	parent='EnterSHORT',
-	label='StopTrailingSHORT'
+	label='StopTrailingSHORT',
+	storefun=FALSE
 )
 }
 
@@ -200,7 +204,8 @@
 	),
 	type='chain',
 	parent='EnterLONG',
-	label='TakeProfitLONG'
+	label='TakeProfitLONG',
+	storefun=FALSE
 )
 
 add.rule(s, name = 'ruleSignal',
@@ -216,7 +221,8 @@
 	),
 	type='chain',
 	parent='EnterSHORT',
-	label='TakeProfitSHORT'
+	label='TakeProfitSHORT',
+	storefun=FALSE
 )
 
 ### 
@@ -232,7 +238,8 @@
 	),
 	type='exit',
 	timespan = .timespan,
-	label='Exit2LONG'
+	label='Exit2LONG',
+	storefun=FALSE
 )
 
 add.rule(s, name = 'ruleSignal',
@@ -246,7 +253,9 @@
 	),
 	type='exit',
 	timespan = .timespan,
-	label='Exit2SHORT')
+	label='Exit2SHORT',
+	storefun=FALSE
+)
 
 add.rule(s, name = 'ruleSignal',
 	arguments=list(sigcol='long' , sigval=TRUE,
@@ -262,7 +271,8 @@
 	),
 	type='enter',
 	timespan = .timespan,
-	label='EnterLONG'
+	label='EnterLONG',
+	storefun=FALSE
 )
 
 add.rule(s, name = 'ruleSignal',
@@ -279,7 +289,8 @@
 	),
 	type='enter',
 	timespan = .timespan,
-	label='EnterSHORT'
+	label='EnterSHORT',
+	storefun=FALSE
 )
 
 #

Modified: pkg/quantstrat/man/add.constraint.Rd
===================================================================
--- pkg/quantstrat/man/add.constraint.Rd	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/man/add.constraint.Rd	2012-10-26 21:07:53 UTC (rev 1231)
@@ -1,33 +1,41 @@
 \name{add.constraint}
 \alias{add.constraint}
-\title{Adds a constraint to 2 distributions within a paramset}
+\title{Adds a constraint on 2 distributions within a paramset}
 \usage{
   add.constraint(strategy, paramset.label,
     distribution.label.1, distribution.label.2, operator,
-    label)
+    label, store = TRUE)
 }
 \arguments{
-  \item{strategy:}{the name of the strategy object}
+  \item{strategy}{the name of the strategy object to add
+  the constraint to}
 
-  \item{paramset.label:}{a label uniquely identifying the
+  \item{paramset.label}{a label uniquely identifying the
   paramset within the strategy}
 
-  \item{distribution.label.1:}{a label identifying the
-  first distribution}
+  \item{distribution.label.1}{a label identifying the first
+  distribution}
 
-  \item{distribution.label.2:}{a label identifying the
+  \item{distribution.label.2}{a label identifying the
   second distribution}
 
-  \item{operator:}{an operator specifying the relational
+  \item{operator}{an operator specifying the relational
   constraint between the 2 distributions}
 
-  \item{label:}{a label uniquely identifying the constraint
+  \item{label}{a label uniquely identifying the constraint
   within the paramset}
 }
 \description{
-  Adds a constraint to 2 distributions within a paramset
+  Creates a constraint on 2 distributions in a paramset,
+  i.e. a restriction limiting the allowed combinations from
+  the ranges for distribution 1 and distribution 2.
 }
 \author{
   Jan Humme
 }
+\seealso{
+  \code{\link{add.distribution}},
+  \code{\link{delete.paramset}},
+  \code{\link{apply.paramset}}
+}
 

Modified: pkg/quantstrat/man/add.distribution.Rd
===================================================================
--- pkg/quantstrat/man/add.distribution.Rd	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/man/add.distribution.Rd	2012-10-26 21:07:53 UTC (rev 1231)
@@ -4,30 +4,38 @@
 \usage{
   add.distribution(strategy, paramset.label,
     component.type, component.label, variable,
-    weight = NULL, label)
+    weight = NULL, label, store = TRUE)
 }
 \arguments{
-  \item{strategy:}{the name of the strategy object}
+  \item{strategy}{the name of the strategy object to add
+  the distribution to}
 
-  \item{paramset.label:}{a label uniquely identifying the
+  \item{paramset.label}{a label uniquely identifying the
   paramset within the strategy}
 
-  \item{component.type:}{one of c('indicator', 'signal',
-  'order', 'enter', 'exit', chain')}
+  \item{component.type}{one of c('indicator', 'signal',
+  'order', 'enter', 'exit', 'chain')}
 
-  \item{component.label:}{a label identifying the
-  component. must be unique per component type}
+  \item{component.label}{a label identifying the component.
+  must be unique per component type}
 
-  \item{variable:}{the name of the variable in the
+  \item{variable}{the name of the variable in the
   component}
 
-  \item{label:}{a label uniquely identifying the
+  \item{label}{a label uniquely identifying the
   distribution within the paramset}
 }
 \description{
-  Adds a distribution to a paramset in a strategy
+  Creates a distribution in paramset, where a distribution
+  consists of the name of a variable in a strategy
+  component plus a range of values for this variable.
 }
 \author{
   Jan Humme
 }
+\seealso{
+  \code{\link{add.constraint}},
+  \code{\link{delete.paramset}},
+  \code{\link{apply.paramset}}
+}
 

Modified: pkg/quantstrat/man/apply.paramset.Rd
===================================================================
--- pkg/quantstrat/man/apply.paramset.Rd	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/man/apply.paramset.Rd	2012-10-26 21:07:53 UTC (rev 1231)
@@ -6,22 +6,39 @@
     nsamples = 0, verbose = FALSE)
 }
 \arguments{
-  \item{strategy:}{the name of the strategy object}
+  \item{strategy}{the name of the strategy object}
 
-  \item{paramset.label:}{a label uniquely identifying the
+  \item{paramset.label}{a label uniquely identifying the
   paramset within the strategy}
 
-  \item{portfolio.st:}{a string variable}
+  \item{portfolio.st}{a string variable}
 
-  \item{nsamples:}{if > 0 then take a sample of only size
+  \item{nsamples}{if > 0 then take a sample of only size
   nsamples from the paramset}
 
-  \item{verbose}{}
+  \item{verbose}{return full information, in particular the
+  .blotter environment, default FALSE}
 }
 \description{
-  Apply a paramset to the strategy
+  This function will run applyStrategy() on portfolio.st,
+  once for each parameter combination as specified by the
+  parameter distributions and constraints in the paramset.
+  Results are gathered and returned as a list containing a
+  slot for each parameter combination.
 }
+\details{
+  apply.paramset uses the foreach package to start the runs
+  for each parameter combination, and as such allows for
+  parallel processing. It is up to the caller to load and
+  register an appropriate backend, eg. doMC, doParallel or
+  doRedis.
+}
 \author{
   Jan Humme
 }
+\seealso{
+  \code{\link{add.constraint}},
+  \code{\link{add.constraint}},
+  \code{\link{delete.paramset}}
+}
 

Modified: pkg/quantstrat/man/delete.paramset.Rd
===================================================================
--- pkg/quantstrat/man/delete.paramset.Rd	2012-10-22 23:21:13 UTC (rev 1230)
+++ pkg/quantstrat/man/delete.paramset.Rd	2012-10-26 21:07:53 UTC (rev 1231)
@@ -2,18 +2,24 @@
 \alias{delete.paramset}
 \title{Delete a paramset from a strategy}
 \usage{
-  delete.paramset(strategy, paramset.label)
+  delete.paramset(strategy, paramset.label, store = TRUE)
 }
 \arguments{
-  \item{strategy:}{the name of the strategy object}
+  \item{strategy}{the name of the strategy object}
 
-  \item{paramset.label:}{a label uniquely identifying the
+  \item{paramset.label}{a label uniquely identifying the
   paramset within the strategy}
 }
 \description{
-  Delete a paramset from a strategy
+  Delete a paramset from a strategy, including its
+  distributions and constraints.
 }
 \author{
   Jan Humme
 }
+\seealso{
+  \code{\link{add.constraint}},
+  \code{\link{add.constraint}},
+  \code{\link{apply.paramset}}
+}
 



More information about the Blotter-commits mailing list