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.

59 lines
1.8 KiB

{-# LANGUAGE FlexibleContexts #-}
7 years ago
{-# LANGUAGE OverloadedStrings #-}
module ATrade.Quotes.QTIS
(
TickerInfo(..),
qtisGetTickersInfo
7 years ago
) where
import ATrade.Exceptions
import ATrade.Logging (Message, logInfo)
7 years ago
import ATrade.Types
import Colog (WithLog)
import Control.Exception.Safe
import Control.Monad.IO.Class (MonadIO (liftIO))
7 years ago
import Data.Aeson
import qualified Data.ByteString.Char8 as BC8
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
7 years ago
import System.ZMQ4
7 years ago
data TickerInfo = TickerInfo {
7 years ago
tiTicker :: T.Text,
tiLotSize :: Integer,
7 years ago
tiTickSize :: Price
} deriving (Show, Eq)
instance FromJSON TickerInfo where
parseJSON = withObject "object" (\obj ->
TickerInfo <$>
obj .: "ticker" <*>
obj .: "lot_size" <*>
obj .: "tick_size")
instance ToJSON TickerInfo where
toJSON ti = object [ "ticker" .= tiTicker ti,
"lot_size" .= tiLotSize ti,
"tick_size" .= tiTickSize ti ]
qtisGetTickersInfo :: (WithLog env Message m, MonadIO m) => Context -> T.Text -> TickerId -> m TickerInfo
qtisGetTickersInfo ctx endpoint tickerId = do
logInfo "QTIS" $ "Requesting ticker: " <> tickerId <> " from " <> endpoint
liftIO $ withSocket ctx Req $ \sock -> do
7 years ago
connect sock $ T.unpack endpoint
send sock [] $ BL.toStrict tickerRequest
response <- receiveMulti sock
let r = parseResponse response
case r of
Just resp -> return resp
Nothing -> throw $ QTISFailure "Can't parse response"
7 years ago
where
tickerRequest = encode $ object ["ticker" .= tickerId]
7 years ago
parseResponse :: [BC8.ByteString] -> Maybe TickerInfo
parseResponse (header:payload:_) = if header == "OK"
then decode $ BL.fromStrict payload
else Nothing
parseResponse _ = Nothing
7 years ago