Execution layer for algorithmic trading
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

167 lines
7.0 KiB

4 years ago
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
4 years ago
module ATrade.Driver.Junction.RobotDriverThread
(
4 years ago
createRobotDriverThread,
RobotEnv(..),
RobotM(..),
RobotDriverHandle,
onStrategyInstance,
postNotificationEvent) where
4 years ago
import ATrade.Broker.Client (BrokerClientHandle)
4 years ago
import qualified ATrade.Broker.Client as Bro
import ATrade.Broker.Protocol (Notification (OrderNotification, TradeNotification))
4 years ago
import ATrade.Driver.Junction.QuoteStream (QuoteStream (addSubscription),
QuoteSubscription (QuoteSubscription))
import ATrade.Driver.Junction.Types (BigConfig,
StrategyDescriptor,
StrategyInstance (StrategyInstance, strategyEventCallback),
StrategyInstanceDescriptor (configKey),
confStrategy, confTickers,
eventCallback, stateKey,
strategyId, tickerId,
timeframe)
import ATrade.QuoteSource.Client (QuoteData (..))
import ATrade.RoboCom.ConfigStorage (ConfigStorage)
4 years ago
import ATrade.RoboCom.Monad (Event (NewBar, NewTick, NewTrade, OrderUpdate),
4 years ago
MonadRobot (..))
import ATrade.RoboCom.Persistence (MonadPersistence)
4 years ago
import ATrade.RoboCom.Types (BarSeriesId (BarSeriesId),
Bars)
4 years ago
import ATrade.Types (OrderId, OrderState, Trade)
import Control.Concurrent (ThreadId, forkIO)
import Control.Concurrent.BoundedChan (BoundedChan,
newBoundedChan, readChan,
writeChan)
4 years ago
import Control.Exception.Safe (MonadThrow)
import Control.Monad (forM_, forever, void)
4 years ago
import Control.Monad.IO.Class (MonadIO, liftIO)
4 years ago
import Control.Monad.Reader (MonadReader, ReaderT, asks)
4 years ago
import Data.Aeson (FromJSON, ToJSON)
import Data.Default
import Data.IORef (IORef, atomicModifyIORef',
readIORef, writeIORef)
4 years ago
import qualified Data.Map.Strict as M
import qualified Data.Text.Lazy as TL
import Data.Time (UTCTime)
4 years ago
import Dhall (FromDhall)
import System.Log.Logger (infoM)
4 years ago
data RobotDriverHandle = forall c s. (FromDhall c, Default s, FromJSON s, ToJSON s) =>
RobotDriverHandle (StrategyInstance c s) ThreadId ThreadId (BoundedChan RobotDriverEvent)
4 years ago
data RobotDriverRequest
data RobotDriverEvent =
EventRequest RobotDriverRequest
| QuoteEvent QuoteData
| NewTradeEvent Trade
| OrderEvent OrderId OrderState
robotDriverThread :: (MonadIO m,
MonadRobot m c s) =>
StrategyInstance c s ->
BoundedChan RobotDriverEvent ->
m ()
robotDriverThread inst eventQueue =
forever $ liftIO (readChan eventQueue) >>= handleEvent
where
handleEvent (EventRequest _) = return ()
handleEvent (QuoteEvent d) =
case d of
QDTick tick -> strategyEventCallback inst (NewTick tick)
QDBar (tf, bar) -> strategyEventCallback inst (NewBar (tf, bar))
handleEvent (NewTradeEvent trade) = strategyEventCallback inst (NewTrade trade)
handleEvent (OrderEvent oid newState) = strategyEventCallback inst (OrderUpdate oid newState)
createRobotDriverThread :: (MonadIO m1,
ConfigStorage m1,
MonadPersistence m1,
QuoteStream m1,
Default s,
4 years ago
FromJSON s,
ToJSON s,
FromDhall c,
MonadIO m,
MonadRobot m c s) =>
StrategyInstanceDescriptor
-> StrategyDescriptor c s
-> (m () -> IO ())
-> BigConfig c
-> IORef c
-> IORef s
-> IORef [UTCTime]
4 years ago
-> m1 RobotDriverHandle
createRobotDriverThread instDesc strDesc runner bigConf rConf rState rTimers = do
4 years ago
eventQueue <- liftIO $ newBoundedChan 2000
let inst = StrategyInstance (strategyId instDesc) (eventCallback strDesc) rState rConf rTimers
4 years ago
quoteQueue <- liftIO $ newBoundedChan 2000
forM_ (confTickers bigConf) (\x -> addSubscription (QuoteSubscription (tickerId x) (timeframe x)) quoteQueue)
qthread <- liftIO . forkIO $ forever $ passQuoteEvents eventQueue quoteQueue
driver <- liftIO . forkIO $ runner $ robotDriverThread inst eventQueue
return $ RobotDriverHandle inst driver qthread eventQueue
where
passQuoteEvents eventQueue quoteQueue = do
v <- readChan quoteQueue
writeChan eventQueue (QuoteEvent v)
4 years ago
onStrategyInstance :: RobotDriverHandle -> forall r. (forall c s. (FromDhall c, Default s, FromJSON s, ToJSON s) => StrategyInstance c s -> r) -> r
onStrategyInstance (RobotDriverHandle inst _ _ _) f = f inst
4 years ago
data RobotEnv c s =
RobotEnv
{
stateRef :: IORef s,
configRef :: IORef c,
timersRef :: IORef [UTCTime],
4 years ago
broker :: BrokerClientHandle,
bars :: IORef Bars
}
newtype RobotM c s a = RobotM { unRobotM :: ReaderT (RobotEnv c s) IO a }
deriving (Functor, Applicative, Monad, MonadReader (RobotEnv c s), MonadIO, MonadThrow)
instance MonadRobot (RobotM c s) c s where
submitOrder order = do
bro <- asks broker
liftIO $ void $ Bro.submitOrder bro order
cancelOrder oid = do
bro <- asks broker
liftIO $ void $ Bro.cancelOrder bro oid
appendToLog = liftIO . infoM "Robot" . TL.unpack
setupTimer t = do
ref <- asks timersRef
liftIO $ atomicModifyIORef' ref (\s -> (t : s, ()))
4 years ago
enqueueIOAction = undefined
getConfig = asks configRef >>= liftIO . readIORef
getState = asks stateRef >>= liftIO . readIORef
setState newState = asks stateRef >>= liftIO . flip writeIORef newState
getEnvironment = undefined
getTicker tid tf = do
b <- asks bars >>= liftIO . readIORef
return $ M.lookup (BarSeriesId tid tf) b
postNotificationEvent :: (MonadIO m) => RobotDriverHandle -> Notification -> m ()
postNotificationEvent (RobotDriverHandle _ _ _ eventQueue) notification = liftIO $
case notification of
OrderNotification _ oid state -> writeChan eventQueue (OrderEvent oid state)
TradeNotification _ trade -> writeChan eventQueue (NewTradeEvent trade)