ATrade-QUIK connector
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.

143 lines
5.6 KiB

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
9 years ago
module Main where
import System.IO
import ATrade.QuoteSource.Server
import ATrade.Types
import Control.Concurrent hiding (readChan,
writeChan)
import Control.Concurrent.BoundedChan
import Control.Error.Util
import Control.Exception.Safe
import Control.Monad
import Data.GI.Base
import qualified GI.Gtk as Gtk
import QuoteSource.DataImport
import QuoteSource.PipeReader
import QuoteSource.TableParser
import QuoteSource.TableParsers.AllParamsTableParser
import ATrade.Broker.Server
import ATrade.Broker.TradeSinks.ZMQTradeSink
import Broker.PaperBroker
import Broker.QuikBroker
import System.Directory
import System.Log.Formatter
import System.Log.Handler (setFormatter)
import System.Log.Handler.Simple
import System.Log.Logger
import System.Timeout
import System.ZMQ4
import System.ZMQ4.ZAP
import Data.Maybe
import qualified Data.Text as T
import Config
import TickTable (mkTickTable)
import Version
9 years ago
8 years ago
forkBoundedChan :: Int -> BoundedChan Tick -> IO (ThreadId, BoundedChan Tick, BoundedChan Tick, BoundedChan QuoteSourceServerData)
9 years ago
forkBoundedChan size sourceChan = do
8 years ago
sink1 <- newBoundedChan size
sink2 <- newBoundedChan size
9 years ago
sinkQss <- newBoundedChan size
tid <- forkIO $ forever $ do
9 years ago
v <- readChan sourceChan
8 years ago
writeChan sink1 v
writeChan sink2 v
9 years ago
writeChan sinkQss (QSSTick v)
8 years ago
return (tid, sink1, sink2, sinkQss)
9 years ago
9 years ago
initLogging :: IO ()
initLogging = do
handler <- streamHandler stderr DEBUG >>=
(\x -> return $
setFormatter x (simpleLogFormatter "$utcTime\t {$loggername} <$prio> -> $msg"))
fhandler <- fileHandler "quik-connector.log" DEBUG >>=
(\x -> return $
setFormatter x (simpleLogFormatter "$utcTime\t {$loggername} <$prio> -> $msg"))
hSetBuffering stderr LineBuffering
updateGlobalLogger rootLoggerName (setLevel DEBUG)
updateGlobalLogger rootLoggerName (setHandlers [handler, fhandler])
9 years ago
main :: IO ()
main = do
initLogging
infoM "main" $ "Starting quik-connector-" ++ T.unpack quikConnectorVersionText
9 years ago
infoM "main" "Loading config"
config <- readConfig "quik-connector.config.json"
9 years ago
infoM "main" "Config loaded"
9 years ago
chan <- newBoundedChan 10000
9 years ago
infoM "main" "Starting data import server"
9 years ago
_ <- initDataImportServer [MkTableParser $ mkAllParamsTableParser "allparams"] chan "atrade"
8 years ago
(forkId, c0, c1, c2) <- forkBoundedChan 10000 chan
withContext (\ctx -> do
8 years ago
tickTable <- mkTickTable c0 ctx (T.pack $ qtisEndpoint config)
brokerQ <- mkQuikBroker tickTable (dllPath config) (quikPath config) (quikAccounts config) (commissions config)
brokerP <- mkPaperBroker tickTable c1 1000000 ["demo"] (commissions config)
withZapHandler ctx (\zap -> do
8 years ago
zapSetWhitelist zap "global" $ whitelist config
zapSetBlacklist zap "global" $ blacklist config
case brokerClientCertificateDir config of
Just certFile -> do
certs <- loadCertificatesFromDirectory certFile
8 years ago
forM_ certs (\cert -> zapAddClientCertificate zap "global" cert)
Nothing -> return ()
serverCert <- case brokerServerCertPath config of
Just certFile -> do
eitherCert <- loadCertificateFromFile certFile
case eitherCert of
Left errorMessage -> do
warningM "main" $ "Unable to load server certificate: " ++ errorMessage
return Nothing
Right cert -> return $ Just cert
Nothing -> return Nothing
let serverParams = defaultServerSecurityParams { sspDomain = Just "global",
sspCertificate = serverCert }
bracket (forkIO $ pipeReaderThread ctx config c2) killThread (\_ -> do
withZMQTradeSink ctx (tradeSink config) (\zmqTradeSink -> do
withZMQTradeSink ctx (tradeSink2 config) (\zmqTradeSink2 -> do
8 years ago
bracket (startQuoteSourceServer c2 ctx (T.pack $ quotesourceEndpoint config) (Just "global")) stopQuoteSourceServer (\_ -> do
bracket (startBrokerServer [brokerP, brokerQ] ctx (T.pack $ brokerserverEndpoint config) [zmqTradeSink2, zmqTradeSink] serverParams) stopBrokerServer (\_ -> do
void $ Gtk.init Nothing
window <- new Gtk.Window [ #title := "Quik connector" ]
void $ on window #destroy Gtk.mainQuit
#showAll window
Gtk.main)
infoM "main" "BRS down")
debugM "main" "QS done")
debugM "main" "TGTS done")
debugM "main" "ZMQTS done")
debugM "main" "ZAP done"))
9 years ago
void $ timeout 1000000 $ killThread forkId
infoM "main" "Main thread done"
where
pipeReaderThread ctx config qsdataChan =
case pipeReaderQsEndpoint config of
Just qsep -> do
infoM "main" $ "QS: " ++ qsep
bracket (startPipeReader ctx (T.pack qsep) qsdataChan) stopPipeReader (\_ -> forever $ threadDelay 1000000)
_ -> return ()
9 years ago
loadCertificatesFromDirectory :: FilePath -> IO [CurveCertificate]
loadCertificatesFromDirectory filepath = do
files <- listDirectory filepath
catMaybes <$> forM files (\file -> hush <$> loadCertificateFromFile file)