[Haskell-cafe] Composing trading strategies (was: Should I step into a minefield? / Writing a trading studio in Haskell)

Greg Fitzgerald garious at gmail.com
Thu Nov 8 14:32:18 EST 2007


> My idea is to write something like TradeStation [1] or NinjaTrader, only
for the Mac.
> It would be quite nifty to use SPJ's financial combinator approach

I was experimenting with a Haskell EDSL for financial trading not too long
ago.  My favorite strategy so far is the parallel parser combinator
approach.  It allows users to run many parallel trading strategies in a nice
single-threaded way that's easy to reason about and straightforward to
compose new trading strategies.

The idea is that the user composes an 'openPosition' and 'closePosition'
trading strategies from a combinator library and gives them to the trading
platform.  The user's trading strategies are nothing more than a numeric
parser combinators.  With each incoming quote, the trading platform kicks
off the user's 'openPosition' trading strategy.  When a strategy succeeds (a
successful parse), the trading platform opens a position for the user.  Once
a position is opened, the platform starts running the user's 'closePosition'
strategy.  The closePosition parser is run the same way and when it
succeeds, the user's position is closed.

To implement, I leveraged Twan van Laarhoven's ParseP library (
http://twan.home.fmf.nl/parsep/), which at least for my simple experiments,
was incredibly complete and stable given its 0.1 version number.   Why
ParseP and not Parsec or ReadP?  Parsec doesn't have an unbiased choice
operator and ReadP only works on strings.

Implementing context-free trading strategies like limit orders is very easy
(limitOrder price = satisfy (>= price)), but context-sensitive strategies,
such as "match the longest string of increasing numbers" is quite a bit more
painful.  Below are some of my experiments (also on hpaste:
http://hpaste.org/3756).  If anybody could offer more elegant solutions, I'd
love to hear because this still feels overly complicated to me.
'testUpThenDown' matches an input stream that increases then decreases.
'testNumericFib' will try to match as much of the Fibonacci sequence as
possible.


import Text.ParserCombinators.ParseP
import qualified Text.ParserCombinators.ParseP.Greedy as Greedy
import Control.Applicative
import Data.Monoid

testUpThenDown = print $ runParser coaster [1, 2, 1]
testNumericFib = print $ runParser (fib (Sum 1) (Sum 1)) (map Sum [2, 3, 5,
7, 1])
testAlphaFib = print $ runParser (fib "a" "b") ["ab", "bab", "cad"]

fib :: (Eq a, Monoid a) => a -> a -> Parser a p [a]
fib n1 n2 = Greedy.option [] (do
   n3 <- satisfy (== (n1 `mappend` n2))
   ns <- fib n2 n3
   return (n3:ns))

coaster :: Ord a => Parser a p ([a], [a])
coaster = do
   seed <- get
   up   <- increasing seed
   down <- decreasing (last up)
   return (seed:up, down)

increasing seed = trend (<) seed
decreasing seed = trend (>) seed

trend :: (Monad (Parser a p)) => (a -> a -> Bool) -> a -> Parser a p [a]
trend f = many1WithContext (satisfy . f)

manyWithContext p = Greedy.option [] . many1WithContext p

many1WithContext p seed = do
   n  <- p seed
   ns <- manyWithContext p n
   return (n:ns)


Thanks,
Greg




On Nov 7, 2007 5:02 PM, Joel Reymont <joelr1 at gmail.com> wrote:

> I need to pick among the usual list of suspects for a commercial
> product that I'm writing. The suspects are OCaml, Haskell and Lisp and
> the product is a trading studio. My idea is to write something like
> TradeStation [1] or NinjaTrader, only for the Mac.
>
> It would be quite nifty to use SPJ's financial combinator approach
> and, for example, embed Yi (Haskell editor).
>
> One of the key features of the product would be the ability to model
> your trading logic using a trading DSL. I'm thinking that this DSL
> could well be Haskell but I'm concerned about stepping into a minefield.
>
> I will need to embed GHC into the app, for example, and I understand
> that the GHC API does not offer unloading of code at the moment. I
> would prefer not to bundle GHC separately so I don't think the hs-
> plugins approach would work for me. Maybe I'm mistaken.
>
> Most of all, I'm concerned that my users will need to face the error
> reports from GHC and could get tripped by laziness, i.e. write
> something that would make the app run out of memory. Off the top of my
> head I can't figure out a way to limit what my users can do without
> analyzing the Haskell AST within the GHC API and complaining if
> necessary.
>
> Can someone with experience in offering a Haskell DSL to their users
> please comment?
>
> Notice that I'm not even mentioning being concerned with the
> unpredictable effects of laziness. There's probably a reason why Jane
> St Capital is using OCaml instead of Haskell. I'm not going to play in
> that league but my knee-jerk reaction is to use OCaml or Lisp and
> avoid laziness altogether. I just can't see how laziness can help in
> processing real-time price data.
>
>        Thanks, Joel
>
> [1] http://www.tradestation.com/default_2.shtm
> [2] http://www.ninjatrader.com/webnew/index.htm
>
> --
> http://wagerlabs.com
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071108/731e632c/attachment.htm


More information about the Haskell-Cafe mailing list