Browse Source

Transaq: changed transaq responses to HKD

master
Denis Tereshkin 2 years ago
parent
commit
06b0b95324
  1. 35
      src/TXMLConnector/Internal.hs
  2. 565
      src/Transaq.hs
  3. 7
      test/Spec.hs
  4. 12
      test/Test/Transaq.hs
  5. 4
      transaq-connector.cabal

35
src/TXMLConnector/Internal.hs

@ -33,6 +33,7 @@ import Control.Concurrent.STM.TBQueue (TBQueue, flushTBQueue,
import Control.Monad (forM_, void, when) import Control.Monad (forM_, void, when)
import Control.Monad.Extra (whileM) import Control.Monad.Extra (whileM)
import qualified Data.Bimap as BM import qualified Data.Bimap as BM
import Data.Functor.Identity (Identity (..))
import Data.Maybe (catMaybes, fromMaybe, mapMaybe) import Data.Maybe (catMaybes, fromMaybe, mapMaybe)
import qualified Data.Text as T import qualified Data.Text as T
import Debug.EventCounters (emitEvent) import Debug.EventCounters (emitEvent)
@ -43,8 +44,10 @@ import Text.XML.Light.Types (Content (Elem),
Element (elName), Element (elName),
QName (qName)) QName (qName))
import TickTable (TickTable, insertTick) import TickTable (TickTable, insertTick)
import Transaq (AllTradesTrade (..), import Transaq (AllTradesTrade,
Candle (..), ClientData (..), AllTradesTradeB (..), Candle,
CandleB (..), ClientData,
ClientDataB (..),
CommandCancelOrder (..), CommandCancelOrder (..),
CommandChangePass (..), CommandChangePass (..),
CommandConnect (..), CommandConnect (..),
@ -54,13 +57,15 @@ import Transaq (AllTradesTrade (..),
CommandSubscribe (..), CommandSubscribe (..),
ConnectionState (Disconnected), ConnectionState (Disconnected),
Language (LanguageEn), Language (LanguageEn),
MarketInfo (..), MarketInfo, MarketInfoB (..),
OrderNotification (..), OrderNotification,
OrderStatus (..), OrderNotificationB (..),
Quotation (..), OrderStatus (..), Quotation,
QuotationB (..),
ResponseAllTrades (ResponseAllTrades), ResponseAllTrades (ResponseAllTrades),
ResponseCandleKinds (ResponseCandleKinds), ResponseCandleKinds (ResponseCandleKinds),
ResponseCandles (..), ResponseCandles,
ResponseCandlesB (..),
ResponseCandlesStatus (StatusPending), ResponseCandlesStatus (StatusPending),
ResponseClient (ResponseClient), ResponseClient (ResponseClient),
ResponseMarkets (ResponseMarkets), ResponseMarkets (ResponseMarkets),
@ -69,8 +74,10 @@ import Transaq (AllTradesTrade (..),
ResponseResult (..), ResponseResult (..),
ResponseSecurities (ResponseSecurities), ResponseSecurities (ResponseSecurities),
ResponseTrades (ResponseTrades), ResponseTrades (ResponseTrades),
Security (..), SecurityId (..), Security, SecurityB (..),
TradeNotification (..), SecurityId (..),
TradeNotification,
TradeNotificationB (..),
TransaqCommand (toXml), TransaqCommand (toXml),
TransaqResponse (..), TransaqResponse (..),
TransaqResponse (..), TransaqResponse (..),
@ -299,6 +306,10 @@ handleTransaqData transaqData = do
pure Nothing pure Nothing
_ -> pure Nothing _ -> pure Nothing
where where
handleTrade :: (MonadIO m,
MonadReader Env m,
HasLog Env Message m) => TradeNotification -> m ()
handleTrade transaqTrade = do handleTrade transaqTrade = do
brState <- asks brokerState brState <- asks brokerState
trIdMap <- liftIO $ readTVarIO (bsOrderTransactionIdMap brState) trIdMap <- liftIO $ readTVarIO (bsOrderTransactionIdMap brState)
@ -318,6 +329,8 @@ handleTransaqData transaqData = do
_ -> log Warning "TXMLConnector.WorkThread" $ "Unable to find order in ordermap: " <> (T.pack . show) transaqTrade _ -> log Warning "TXMLConnector.WorkThread" $ "Unable to find order in ordermap: " <> (T.pack . show) transaqTrade
Nothing -> log Warning "TXMLConnector.WorkThread" "No callback for trade notification!" Nothing -> log Warning "TXMLConnector.WorkThread" "No callback for trade notification!"
fromTransaqTrade :: TradeNotification -> Order -> Maybe TickerInfo -> Trade
fromTransaqTrade transaqTrade order maybeTickerInfo = fromTransaqTrade transaqTrade order maybeTickerInfo =
let vol = case maybeTickerInfo of let vol = case maybeTickerInfo of
Just tickerInfo -> fromIntegral (tQuantity transaqTrade) * tPrice transaqTrade / tiTickSize tickerInfo * tiTickPrice tickerInfo Just tickerInfo -> fromIntegral (tQuantity transaqTrade) * tPrice transaqTrade / tiTickSize tickerInfo * tiTickPrice tickerInfo
@ -340,6 +353,9 @@ handleTransaqData transaqData = do
fromDirection Transaq.Buy = AT.Buy fromDirection Transaq.Buy = AT.Buy
fromDirection Transaq.Sell = AT.Sell fromDirection Transaq.Sell = AT.Sell
handleOrder :: (MonadIO m,
MonadReader Env m,
HasLog Env Message m) => OrderNotification -> m ()
handleOrder orderUpdate = do handleOrder orderUpdate = do
brState <- asks brokerState brState <- asks brokerState
trIdMap <- liftIO $ readTVarIO (bsOrderTransactionIdMap brState) trIdMap <- liftIO $ readTVarIO (bsOrderTransactionIdMap brState)
@ -358,6 +374,7 @@ handleTransaqData transaqData = do
_ -> log Warning "TXMLConnector.WorkThread" "Unable to find order for order notification" _ -> log Warning "TXMLConnector.WorkThread" "Unable to find order for order notification"
Nothing -> log Warning "TXMLConnector.WorkThread" "No callback for order notification" Nothing -> log Warning "TXMLConnector.WorkThread" "No callback for order notification"
orderStateFromTransaq :: OrderNotification -> OrderState
orderStateFromTransaq orderUpdate = orderStateFromTransaq orderUpdate =
case oStatus orderUpdate of case oStatus orderUpdate of
OrderActive -> Submitted OrderActive -> Submitted

565
src/Transaq.hs

@ -1,6 +1,12 @@
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
module Transaq module Transaq
( (
@ -19,36 +25,52 @@ module Transaq
CommandGetHistoryData(..), CommandGetHistoryData(..),
CommandChangePass(..), CommandChangePass(..),
ResponseResult(..), ResponseResult(..),
ResponseCandles(..), ResponseCandles,
ResponseServerStatus(..), ResponseCandlesB(..),
ResponseServerStatus,
ResponseServerStatusB(..),
ResponseCandleKinds(..), ResponseCandleKinds(..),
ResponseMarkets(..), ResponseMarkets(..),
ResponseSecurities(..), ResponseSecurities(..),
ResponseSecInfo(..), ResponseSecInfo,
ResponseSecInfoB(..),
ResponseQuotations(..), ResponseQuotations(..),
ResponseAllTrades(..), ResponseAllTrades(..),
ResponseTrades(..), ResponseTrades(..),
ResponseQuotes(..), ResponseQuotes(..),
ResponseOrders(..), ResponseOrders(..),
ResponseClient(..), ResponseClient(..),
ClientData(..), ClientData,
Quotation(..), ClientDataB(..),
Quote(..), Quotation,
TradeNotification(..), QuotationB(..),
OrderNotification(..), Quote,
QuoteB(..),
TradeNotification,
TradeNotificationB(..),
OrderNotification,
OrderNotificationB(..),
OrderStatus(..), OrderStatus(..),
AllTradesTrade(..), AllTradesTrade,
Tick(..), AllTradesTradeB(..),
Tick,
TickB(..),
ConnectionState(..), ConnectionState(..),
MarketInfo(..), MarketInfo,
Security(..), MarketInfoB(..),
CandleKind(..), Security,
SecurityB(..),
CandleKind,
CandleKindB(..),
ResponseCandlesStatus(..), ResponseCandlesStatus(..),
Candle(..), Candle,
CandleB(..),
UnfilledAction(..), UnfilledAction(..),
TradeDirection(..) TradeDirection(..)
) where ) where
import Barbies
import Barbies.Bare
import Control.Applicative ((<|>)) import Control.Applicative ((<|>))
import Control.Error.Util (hush) import Control.Error.Util (hush)
import Control.Monad (void) import Control.Monad (void)
@ -56,12 +78,14 @@ import Data.Attoparsec.Text (Parser, char, decimal, many',
maybeResult, parse, parseOnly, maybeResult, parse, parseOnly,
skipSpace) skipSpace)
import Data.Decimal (DecimalRaw (..)) import Data.Decimal (DecimalRaw (..))
import Data.Functor.Identity (Identity (..))
import Data.Int (Int64) import Data.Int (Int64)
import Data.Maybe (catMaybes, fromMaybe, mapMaybe, import Data.Maybe (catMaybes, fromMaybe, mapMaybe,
maybeToList) maybeToList)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Time (fromGregorian) import Data.Time (fromGregorian)
import Data.Time.Clock (UTCTime (UTCTime)) import Data.Time.Clock (UTCTime (UTCTime))
import GHC.Generics
import Text.Read (readMaybe) import Text.Read (readMaybe)
import Text.XML.Light (Attr (..), CData (cdData), import Text.XML.Light (Attr (..), CData (cdData),
Element (elName), Node (..), QName (..), Element (elName), Node (..), QName (..),
@ -122,8 +146,8 @@ parseTimestamp = hush . parseOnly parser
class TransaqCommand t where class TransaqCommand t where
toXml :: t -> T.Text toXml :: t -> T.Text
class TransaqResponseC t where class TransaqResponseC ctx t where
fromXml :: Element -> Maybe t fromXml :: ctx -> Maybe t
data CommandConnect = data CommandConnect =
CommandConnect CommandConnect
@ -339,7 +363,7 @@ data ResponseResult =
| ResponseFailure T.Text | ResponseFailure T.Text
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseResult where instance TransaqResponseC Element ResponseResult where
fromXml root = fromXml root =
if qName (elName root) == "result" if qName (elName root) == "result"
then then
@ -349,17 +373,27 @@ instance TransaqResponseC ResponseResult where
else Nothing else Nothing
data Candle = data CandleB t f =
Candle Candle
{ {
cTimestamp :: !UTCTime cTimestamp :: Wear t f UTCTime
, cOpen :: !Double , cOpen :: Wear t f Double
, cHigh :: !Double , cHigh :: Wear t f Double
, cLow :: !Double , cLow :: Wear t f Double
, cClose :: !Double , cClose :: Wear t f Double
, cVolume :: !Int , cVolume :: Wear t f Int
, cOpenInterest :: !Int , cOpenInterest :: Wear t f Int
} deriving (Show, Eq, Ord) } deriving (Generic)
type Candle = CandleB Bare Identity
deriving instance FunctorB (CandleB Covered)
deriving instance TraversableB (CandleB Covered)
deriving instance ConstraintsB (CandleB Covered)
deriving instance Show Candle
deriving instance Eq Candle
deriving instance Ord Candle
deriving instance BareB CandleB
data ResponseCandlesStatus = data ResponseCandlesStatus =
StatusEndOfHistory StatusEndOfHistory
@ -368,14 +402,24 @@ data ResponseCandlesStatus =
| StatusUnavaliable | StatusUnavaliable
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
data ResponseCandles = data ResponseCandlesB t f =
ResponseCandles ResponseCandles
{ {
cPeriodId :: !Int cPeriodId :: Wear t f Int
, cStatus :: !ResponseCandlesStatus , cStatus :: Wear t f ResponseCandlesStatus
, cSecurity :: !SecurityId , cSecurity :: Wear t f SecurityId
, cCandles :: ![Candle] , cCandles :: Wear t f [Candle]
} deriving (Show, Eq, Ord) } deriving (Generic)
type ResponseCandles = ResponseCandlesB Bare Identity
deriving instance FunctorB (ResponseCandlesB Covered)
deriving instance TraversableB (ResponseCandlesB Covered)
deriving instance ConstraintsB (ResponseCandlesB Covered)
deriving instance Show ResponseCandles
deriving instance Eq ResponseCandles
deriving instance Ord ResponseCandles
deriving instance BareB ResponseCandlesB
uname :: String -> QName uname :: String -> QName
uname x = blank_name {qName = x} uname x = blank_name {qName = x}
@ -383,20 +427,20 @@ uname x = blank_name {qName = x}
childContent :: String -> Element -> Maybe String childContent :: String -> Element -> Maybe String
childContent tag el = strContent <$> findChild (uname tag) el childContent tag el = strContent <$> findChild (uname tag) el
instance TransaqResponseC ResponseCandles where instance TransaqResponseC Element (ResponseCandlesB Bare f) where
fromXml root = do fromXml root = do
!periodId <- findAttr (uname "period") root >>= readMaybe !periodId <- findAttr (uname "period") root >>= readMaybe
!status <- findAttr (uname "status") root >>= readMaybe >>= parseStatus !status <- findAttr (uname "status") root >>= readMaybe >>= parseStatus
!board <- T.pack <$> findAttr (uname "board") root !board <- T.pack <$> findAttr (uname "board") root
!seccode <- T.pack <$> findAttr (uname "seccode") root !seccode <- T.pack <$> findAttr (uname "seccode") root
let !candles = mapMaybe parseCandle . elChildren $ root let !candles = mapMaybe parseCandle . elChildren $ root
return ResponseCandles return (ResponseCandles
{ {
cPeriodId = periodId cPeriodId = periodId
, cStatus = status , cStatus = status
, cSecurity = SecurityId board seccode , cSecurity = SecurityId board seccode
, cCandles = candles , cCandles = candles
} } :: ResponseCandlesB Bare f)
where where
parseStatus :: Int -> Maybe ResponseCandlesStatus parseStatus :: Int -> Maybe ResponseCandlesStatus
parseStatus intStatus = parseStatus intStatus =
@ -414,7 +458,7 @@ instance TransaqResponseC ResponseCandles where
!close <- findAttr (uname "close") element >>= readMaybe !close <- findAttr (uname "close") element >>= readMaybe
!volume <- findAttr (uname "volume") element >>= readMaybe !volume <- findAttr (uname "volume") element >>= readMaybe
let !openInterest = fromMaybe 0 $ findAttr (uname "oi") element >>= readMaybe let !openInterest = fromMaybe 0 $ findAttr (uname "oi") element >>= readMaybe
return Candle return (Candle
{ {
cTimestamp = timestamp cTimestamp = timestamp
, cOpen = open , cOpen = open
@ -423,7 +467,7 @@ instance TransaqResponseC ResponseCandles where
, cClose = close , cClose = close
, cVolume = volume , cVolume = volume
, cOpenInterest = openInterest , cOpenInterest = openInterest
} } :: CandleB Bare f)
data ConnectionState = data ConnectionState =
Connected Connected
@ -431,18 +475,28 @@ data ConnectionState =
| Error T.Text | Error T.Text
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
data ResponseServerStatus = data ResponseServerStatusB t f =
ResponseServerStatus ResponseServerStatus
{ {
serverId :: !(Maybe Int) serverId :: Wear t f (Maybe Int)
, state :: !ConnectionState , state :: Wear t f ConnectionState
, recover :: !(Maybe Bool) , recover :: Wear t f (Maybe Bool)
, serverTimezone :: !(Maybe T.Text) , serverTimezone :: Wear t f (Maybe T.Text)
, systemVersion :: !(Maybe Int) , systemVersion :: Wear t f (Maybe Int)
, build :: !(Maybe Int) , build :: Wear t f (Maybe Int)
} deriving (Show, Eq, Ord) } deriving (Generic)
instance TransaqResponseC ResponseServerStatus where type ResponseServerStatus = ResponseServerStatusB Bare Identity
deriving instance FunctorB (ResponseServerStatusB Covered)
deriving instance TraversableB (ResponseServerStatusB Covered)
deriving instance ConstraintsB (ResponseServerStatusB Covered)
deriving instance Show ResponseServerStatus
deriving instance Eq ResponseServerStatus
deriving instance Ord ResponseServerStatus
deriving instance BareB ResponseServerStatusB
instance TransaqResponseC Element ResponseServerStatus where
fromXml root = do fromXml root = do
let !serverId = findAttr (uname "id") root >>= readMaybe let !serverId = findAttr (uname "id") root >>= readMaybe
!connectedStr <- findAttr (uname "connected") root !connectedStr <- findAttr (uname "connected") root
@ -460,16 +514,26 @@ instance TransaqResponseC ResponseServerStatus where
let !build = findAttr (uname "build") root >>= readMaybe let !build = findAttr (uname "build") root >>= readMaybe
pure $ ResponseServerStatus {..} pure $ ResponseServerStatus {..}
data MarketInfo = data MarketInfoB t f =
MarketInfo MarketInfo
{ marketId :: !Int { marketId :: Wear t f Int
, marketName :: !T.Text , marketName :: Wear t f T.Text
} deriving (Show, Eq, Ord) } deriving (Generic)
type MarketInfo = MarketInfoB Bare Identity
deriving instance FunctorB (MarketInfoB Covered)
deriving instance TraversableB (MarketInfoB Covered)
deriving instance ConstraintsB (MarketInfoB Covered)
deriving instance Show MarketInfo
deriving instance Eq MarketInfo
deriving instance Ord MarketInfo
deriving instance BareB MarketInfoB
newtype ResponseMarkets = ResponseMarkets [MarketInfo] newtype ResponseMarkets = ResponseMarkets [MarketInfo]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseMarkets where instance TransaqResponseC Element ResponseMarkets where
fromXml root = do fromXml root = do
!markets <- mapM parseMarketInfo $ elChildren root !markets <- mapM parseMarketInfo $ elChildren root
pure . ResponseMarkets . catMaybes $ markets pure . ResponseMarkets . catMaybes $ markets
@ -479,24 +543,34 @@ instance TransaqResponseC ResponseMarkets where
then do then do
!marketId <- findAttr (uname "id") tag >>= readMaybe !marketId <- findAttr (uname "id") tag >>= readMaybe
let !marketName = T.pack $ strContent tag let !marketName = T.pack $ strContent tag
pure $ Just $ MarketInfo {..} pure $ Just $ (MarketInfo {..} :: MarketInfo)
else pure Nothing else pure Nothing
data ClientData = data ClientDataB t f =
ClientData ClientData
{ {
cClientId :: !T.Text cClientId :: Wear t f T.Text
, cType :: !T.Text , cType :: Wear t f T.Text
, cCurrency :: !T.Text , cCurrency :: Wear t f T.Text
, cMarket :: !T.Text , cMarket :: Wear t f T.Text
, cUnion :: !T.Text , cUnion :: Wear t f T.Text
, cForts :: !(Maybe T.Text) , cForts :: Wear t f (Maybe T.Text)
} deriving (Show, Eq, Ord) } deriving (Generic)
type ClientData = ClientDataB Bare Identity
deriving instance FunctorB (ClientDataB Covered)
deriving instance TraversableB (ClientDataB Covered)
deriving instance ConstraintsB (ClientDataB Covered)
deriving instance Show ClientData
deriving instance Eq ClientData
deriving instance Ord ClientData
deriving instance BareB ClientDataB
newtype ResponseClient = ResponseClient ClientData newtype ResponseClient = ResponseClient ClientData
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseClient where instance TransaqResponseC Element ResponseClient where
fromXml root = if (qName . elName) root == "client" fromXml root = if (qName . elName) root == "client"
then do then do
!cClientId <- T.pack <$> findAttr (uname "id") root !cClientId <- T.pack <$> findAttr (uname "id") root
@ -508,19 +582,28 @@ instance TransaqResponseC ResponseClient where
Just $ ResponseClient $ ClientData {..} Just $ ResponseClient $ ClientData {..}
else Nothing else Nothing
data CandleKind = data CandleKindB t f=
CandleKind CandleKind
{ {
kCandleKindId :: !Int kCandleKindId :: Wear t f Int
, kPeriod :: !Int , kPeriod :: Wear t f Int
, kName :: !T.Text , kName :: Wear t f T.Text
} deriving (Show, Eq, Ord) } deriving (Generic)
type CandleKind = CandleKindB Bare Identity
deriving instance FunctorB (CandleKindB Covered)
deriving instance TraversableB (CandleKindB Covered)
deriving instance ConstraintsB (CandleKindB Covered)
deriving instance Show CandleKind
deriving instance Eq CandleKind
deriving instance Ord CandleKind
deriving instance BareB CandleKindB
newtype ResponseCandleKinds = ResponseCandleKinds [CandleKind] newtype ResponseCandleKinds = ResponseCandleKinds [CandleKind]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC Element ResponseCandleKinds where
instance TransaqResponseC ResponseCandleKinds where
fromXml root = do fromXml root = do
!kinds <- mapM parseCandleKind $ elChildren root !kinds <- mapM parseCandleKind $ elChildren root
pure . ResponseCandleKinds . catMaybes $ kinds pure . ResponseCandleKinds . catMaybes $ kinds
@ -531,33 +614,43 @@ instance TransaqResponseC ResponseCandleKinds where
!kCandleKindId <- childContent "id" tag >>= readMaybe !kCandleKindId <- childContent "id" tag >>= readMaybe
!kPeriod <- childContent "period" tag >>= readMaybe !kPeriod <- childContent "period" tag >>= readMaybe
!kName <- T.pack <$> childContent "name" tag !kName <- T.pack <$> childContent "name" tag
pure . Just $ CandleKind {..} pure . Just $ (CandleKind {..} :: CandleKind)
else pure Nothing else pure Nothing
data Security = data SecurityB t f =
Security Security
{ {
sSecId :: !Int sSecId :: Wear t f Int
, sActive :: !Bool , sActive :: Wear t f Bool
, sSeccode :: !T.Text , sSeccode :: Wear t f T.Text
, sInstrClass :: !T.Text , sInstrClass :: Wear t f T.Text
, sBoard :: !T.Text , sBoard :: Wear t f T.Text
, sMarket :: !T.Text , sMarket :: Wear t f T.Text
, sCurrency :: !T.Text , sCurrency :: Wear t f T.Text
, sShortName :: !T.Text , sShortName :: Wear t f T.Text
, sDecimals :: !Int , sDecimals :: Wear t f Int
, sMinStep :: !Double , sMinStep :: Wear t f Double
, sLotSize :: !Int , sLotSize :: Wear t f Int
, sLotDivider :: !Int , sLotDivider :: Wear t f Int
, sPointCost :: !Double , sPointCost :: Wear t f Double
, sSecType :: !T.Text , sSecType :: Wear t f T.Text
} deriving (Show, Eq, Ord) } deriving (Generic)
type Security = SecurityB Bare Identity
deriving instance FunctorB (SecurityB Covered)
deriving instance TraversableB (SecurityB Covered)
deriving instance ConstraintsB (SecurityB Covered)
deriving instance Show Security
deriving instance Eq Security
deriving instance Ord Security
deriving instance BareB SecurityB
newtype ResponseSecurities = newtype ResponseSecurities =
ResponseSecurities [Security] ResponseSecurities [Security]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseSecurities where instance TransaqResponseC Element ResponseSecurities where
fromXml root = do fromXml root = do
securities <- mapM parseSecurity $ elChildren root securities <- mapM parseSecurity $ elChildren root
pure . ResponseSecurities . catMaybes $ securities pure . ResponseSecurities . catMaybes $ securities
@ -579,7 +672,7 @@ instance TransaqResponseC ResponseSecurities where
!sLotDivider <- childContent "lotdivider" tag >>= readMaybe !sLotDivider <- childContent "lotdivider" tag >>= readMaybe
!sPointCost <- childContent "point_cost" tag >>= readMaybe !sPointCost <- childContent "point_cost" tag >>= readMaybe
!sSecType <- T.pack <$> childContent "sectype" tag !sSecType <- T.pack <$> childContent "sectype" tag
pure . Just $ Security {..} pure . Just $ (Security {..} :: Security)
else else
pure Nothing pure Nothing
@ -588,22 +681,31 @@ instance TransaqResponseC ResponseSecurities where
parseBool _ = Nothing parseBool _ = Nothing
data ResponseSecInfo = data ResponseSecInfoB t f =
ResponseSecInfo ResponseSecInfo
{ {
secId :: !Int secId :: Wear t f Int
, secName :: !T.Text , secName :: Wear t f T.Text
, secCode :: !T.Text , secCode :: Wear t f T.Text
, market :: !Int , market :: Wear t f Int
, pname :: !T.Text , pname :: Wear t f T.Text
, clearingPrice :: !Double , clearingPrice :: Wear t f Double
, minprice :: !Double , minprice :: Wear t f Double
, maxprice :: !Double , maxprice :: Wear t f Double
, pointCost :: !Double , pointCost :: Wear t f Double
} deriving (Show, Eq, Ord) } deriving (Generic)
type ResponseSecInfo = ResponseSecInfoB Bare Identity
instance TransaqResponseC ResponseSecInfo where
deriving instance FunctorB (ResponseSecInfoB Covered)
deriving instance TraversableB (ResponseSecInfoB Covered)
deriving instance ConstraintsB (ResponseSecInfoB Covered)
deriving instance Show ResponseSecInfo
deriving instance Eq ResponseSecInfo
deriving instance Ord ResponseSecInfo
deriving instance BareB ResponseSecInfoB
instance TransaqResponseC Element ResponseSecInfo where
fromXml tag = do fromXml tag = do
secId <- findAttr (uname "secid") tag >>= readMaybe secId <- findAttr (uname "secid") tag >>= readMaybe
secName <- T.pack <$> childContent "secname" tag secName <- T.pack <$> childContent "secname" tag
@ -616,36 +718,46 @@ instance TransaqResponseC ResponseSecInfo where
pointCost <- childContent "point_cost" tag >>= readMaybe pointCost <- childContent "point_cost" tag >>= readMaybe
pure ResponseSecInfo {..} pure ResponseSecInfo {..}
data Quotation = data QuotationB t f =
Quotation Quotation
{ {
qSecId :: !Int qSecId :: Wear t f Int
, qBoard :: !T.Text , qBoard :: Wear t f T.Text
, qSeccode :: !T.Text , qSeccode :: Wear t f T.Text
, qOpen :: !(Maybe Double) , qOpen :: Maybe Double
, qWaprice :: !(Maybe Double) , qWaprice :: Maybe Double
, qBidDepth :: !(Maybe Int) , qBidDepth :: Maybe Int
, qBidDepthT :: !(Maybe Int) , qBidDepthT :: Maybe Int
, qNumBids :: !(Maybe Int) , qNumBids :: Maybe Int
, qOfferDepth :: !(Maybe Int) , qOfferDepth :: Maybe Int
, qOfferDepthT :: !(Maybe Int) , qOfferDepthT :: Maybe Int
, qBid :: !(Maybe Double) , qBid :: Maybe Double
, qOffer :: !(Maybe Double) , qOffer :: Maybe Double
, qNumOffers :: !(Maybe Int) , qNumOffers :: Maybe Int
, qNumTrades :: !(Maybe Int) , qNumTrades :: Maybe Int
, qVolToday :: !(Maybe Int) , qVolToday :: Maybe Int
, qOpenPositions :: !(Maybe Int) , qOpenPositions :: Maybe Int
, qLastPrice :: !(Maybe Double) , qLastPrice :: Maybe Double
, qQuantity :: !(Maybe Int) , qQuantity :: Maybe Int
, qTimestamp :: !UTCTime , qTimestamp :: Wear t f UTCTime
, qValToday :: !(Maybe Double) , qValToday :: Maybe Double
} deriving (Show, Eq, Ord) } deriving (Generic)
type Quotation = QuotationB Bare Identity
deriving instance FunctorB (QuotationB Covered)
deriving instance TraversableB (QuotationB Covered)
deriving instance ConstraintsB (QuotationB Covered)
deriving instance Show Quotation
deriving instance Eq Quotation
deriving instance Ord Quotation
deriving instance BareB QuotationB
newtype ResponseQuotations = newtype ResponseQuotations =
ResponseQuotations [Quotation] ResponseQuotations [Quotation]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseQuotations where instance TransaqResponseC Element ResponseQuotations where
fromXml root = do fromXml root = do
quotations <- mapM parseQuotation $ elChildren root quotations <- mapM parseQuotation $ elChildren root
pure . ResponseQuotations . catMaybes $ quotations pure . ResponseQuotations . catMaybes $ quotations
@ -671,7 +783,7 @@ instance TransaqResponseC ResponseQuotations where
let !qQuantity = childContent "quantity" tag >>= readMaybe let !qQuantity = childContent "quantity" tag >>= readMaybe
!qTimestamp <- childContent "time" tag >>= (parseTimestamp . T.pack) !qTimestamp <- childContent "time" tag >>= (parseTimestamp . T.pack)
let !qValToday = childContent "valToday" tag >>= readMaybe let !qValToday = childContent "valToday" tag >>= readMaybe
pure $ Just Quotation {..} pure $ Just (Quotation {..} :: Quotation)
data TradingPeriod = data TradingPeriod =
PeriodOpen PeriodOpen
@ -680,20 +792,30 @@ data TradingPeriod =
| PeriodUnknown | PeriodUnknown
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
data AllTradesTrade = data AllTradesTradeB t f =
AllTradesTrade AllTradesTrade
{ {
attSecId :: !Int attSecId :: Wear t f Int
, attSecCode :: !T.Text , attSecCode :: Wear t f T.Text
, attTradeNo :: !Int64 , attTradeNo :: Wear t f Int64
, attTimestamp :: !UTCTime , attTimestamp :: Wear t f UTCTime
, attBoard :: !T.Text , attBoard :: Wear t f T.Text
, attPrice :: !Double , attPrice :: Wear t f Double
, attQuantity :: !Int , attQuantity :: Wear t f Int
, attBuysell :: !TradeDirection , attBuysell :: Wear t f TradeDirection
, attOpenInterest :: !Int , attOpenInterest :: Wear t f Int
, attPeriod :: !TradingPeriod , attPeriod :: Wear t f TradingPeriod
} deriving (Show, Eq, Ord) } deriving (Generic)
type AllTradesTrade = AllTradesTradeB Bare Identity
deriving instance FunctorB (AllTradesTradeB Covered)
deriving instance TraversableB (AllTradesTradeB Covered)
deriving instance ConstraintsB (AllTradesTradeB Covered)
deriving instance Show AllTradesTrade
deriving instance Eq AllTradesTrade
deriving instance Ord AllTradesTrade
deriving instance BareB AllTradesTradeB
newtype ResponseAllTrades = newtype ResponseAllTrades =
ResponseAllTrades [AllTradesTrade] ResponseAllTrades [AllTradesTrade]
@ -706,7 +828,7 @@ parseTradeDirection t =
"S" -> Just Sell "S" -> Just Sell
_ -> Nothing _ -> Nothing
instance TransaqResponseC ResponseAllTrades where instance TransaqResponseC Element ResponseAllTrades where
fromXml root = do fromXml root = do
alltrades <- mapM parseAllTrade $ elChildren root alltrades <- mapM parseAllTrade $ elChildren root
pure . ResponseAllTrades . catMaybes $ alltrades pure . ResponseAllTrades . catMaybes $ alltrades
@ -722,7 +844,7 @@ instance TransaqResponseC ResponseAllTrades where
!attBuysell <- T.pack <$> childContent "buysell" tag >>= parseTradeDirection !attBuysell <- T.pack <$> childContent "buysell" tag >>= parseTradeDirection
let !attOpenInterest = fromMaybe 0 $ childContent "openinterest" tag >>= readMaybe let !attOpenInterest = fromMaybe 0 $ childContent "openinterest" tag >>= readMaybe
let !attPeriod = fromMaybe PeriodUnknown $ childContent "period" tag >>= parseTradingPeriod let !attPeriod = fromMaybe PeriodUnknown $ childContent "period" tag >>= parseTradingPeriod
pure . Just $ AllTradesTrade {..} pure . Just $ (AllTradesTrade {..} :: AllTradesTrade)
parseTradingPeriod :: String -> Maybe TradingPeriod parseTradingPeriod :: String -> Maybe TradingPeriod
parseTradingPeriod "O" = Just PeriodOpen parseTradingPeriod "O" = Just PeriodOpen
@ -731,24 +853,34 @@ instance TransaqResponseC ResponseAllTrades where
parseTradingPeriod _ = Nothing parseTradingPeriod _ = Nothing
data Quote = data QuoteB t f =
Quote Quote
{ {
secId :: !Int secId :: Wear t f Int
, board :: !T.Text , board :: Wear t f T.Text
, secCode :: !T.Text , secCode :: Wear t f T.Text
, price :: !Double , price :: Wear t f Double
, source :: T.Text , source :: Wear t f T.Text
, yield :: !Int , yield :: Wear t f Int
, buy :: !Int , buy :: Wear t f Int
, sell :: !Int , sell :: Wear t f Int
} deriving (Show, Eq, Ord) } deriving (Generic)
type Quote = QuoteB Bare Identity
deriving instance FunctorB (QuoteB Covered)
deriving instance TraversableB (QuoteB Covered)
deriving instance ConstraintsB (QuoteB Covered)
deriving instance Show Quote
deriving instance Eq Quote
deriving instance Ord Quote
deriving instance BareB QuoteB
newtype ResponseQuotes = newtype ResponseQuotes =
ResponseQuotes [Quote] ResponseQuotes [Quote]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseQuotes where instance TransaqResponseC Element ResponseQuotes where
fromXml root = do fromXml root = do
quotes <- mapM parseQuote $ elChildren root quotes <- mapM parseQuote $ elChildren root
pure . ResponseQuotes . catMaybes $ quotes pure . ResponseQuotes . catMaybes $ quotes
@ -762,7 +894,7 @@ instance TransaqResponseC ResponseQuotes where
!yield <- childContent "yield" tag >>= readMaybe !yield <- childContent "yield" tag >>= readMaybe
!buy <- childContent "buy" tag >>= readMaybe !buy <- childContent "buy" tag >>= readMaybe
!sell <- childContent "sell" tag >>= readMaybe !sell <- childContent "sell" tag >>= readMaybe
return . Just $ Quote {..} return . Just $ (Quote {..} :: Quote)
data OrderStatus = data OrderStatus =
OrderActive OrderActive
@ -781,31 +913,41 @@ data OrderStatus =
| OrderWatching | OrderWatching
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
data OrderNotification = data OrderNotificationB t f =
OrderNotification OrderNotification
{ {
oTransactionId :: !Int oTransactionId :: Wear t f Int
, oOrderNo :: !Int64 , oOrderNo :: Wear t f Int64
, oSecId :: !Int , oSecId :: Wear t f Int
, oBoard :: !T.Text , oBoard :: Wear t f T.Text
, oSecCode :: !T.Text , oSecCode :: Wear t f T.Text
, oClient :: !T.Text , oClient :: Wear t f T.Text
, oUnion :: !T.Text , oUnion :: Wear t f T.Text
, oStatus :: !OrderStatus , oStatus :: Wear t f OrderStatus
, oBuysell :: !TradeDirection , oBuysell :: Wear t f TradeDirection
, oTimestamp :: !UTCTime , oTimestamp :: Wear t f UTCTime
, oBrokerRef :: !T.Text , oBrokerRef :: Wear t f T.Text
, oBalance :: !Int , oBalance :: Wear t f Int
, oPrice :: !Double , oPrice :: Wear t f Double
, oQuantity :: !Int , oQuantity :: Wear t f Int
, oResult :: !T.Text , oResult :: Wear t f T.Text
} deriving (Show, Eq, Ord) } deriving (Generic)
type OrderNotification = OrderNotificationB Bare Identity
deriving instance FunctorB (OrderNotificationB Covered)
deriving instance TraversableB (OrderNotificationB Covered)
deriving instance ConstraintsB (OrderNotificationB Covered)
deriving instance Show OrderNotification
deriving instance Eq OrderNotification
deriving instance Ord OrderNotification
deriving instance BareB OrderNotificationB
newtype ResponseOrders = newtype ResponseOrders =
ResponseOrders [OrderNotification] ResponseOrders [OrderNotification]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseOrders where instance TransaqResponseC Element ResponseOrders where
fromXml root = do fromXml root = do
quotes <- mapM parseOrder $ elChildren root quotes <- mapM parseOrder $ elChildren root
pure . ResponseOrders . catMaybes $ quotes pure . ResponseOrders . catMaybes $ quotes
@ -826,7 +968,7 @@ instance TransaqResponseC ResponseOrders where
!oPrice <- childContent "price" tag >>= readMaybe !oPrice <- childContent "price" tag >>= readMaybe
!oQuantity <- childContent "quantity" tag >>= readMaybe !oQuantity <- childContent "quantity" tag >>= readMaybe
!oResult <- T.pack <$> childContent "result" tag !oResult <- T.pack <$> childContent "result" tag
return . Just $ OrderNotification {..} return . Just $ (OrderNotification {..} :: OrderNotification)
parseStatus "active" = Just OrderActive parseStatus "active" = Just OrderActive
parseStatus "cancelled" = Just OrderCancelled parseStatus "cancelled" = Just OrderCancelled
parseStatus "denied" = Just OrderDenied parseStatus "denied" = Just OrderDenied
@ -843,29 +985,39 @@ instance TransaqResponseC ResponseOrders where
parseStatus "watching" = Just OrderWatching parseStatus "watching" = Just OrderWatching
parseStatus _ = Nothing parseStatus _ = Nothing
data TradeNotification = data TradeNotificationB t f =
TradeNotification TradeNotification
{ {
tSecId :: !Int tSecId :: Wear t f Int
, tTradeNo :: !Int64 , tTradeNo :: Wear t f Int64
, tOrderNo :: !Int64 , tOrderNo :: Wear t f Int64
, tBoard :: !T.Text , tBoard :: Wear t f T.Text
, tSecCode :: !T.Text , tSecCode :: Wear t f T.Text
, tClient :: !T.Text , tClient :: Wear t f T.Text
, tUnion :: !T.Text , tUnion :: Wear t f T.Text
, tBuysell :: !TradeDirection , tBuysell :: Wear t f TradeDirection
, tTimestamp :: !UTCTime , tTimestamp :: Wear t f UTCTime
, tValue :: !Double , tValue :: Wear t f Double
, tComission :: !Double , tComission :: Wear t f Double
, tQuantity :: !Int , tQuantity :: Wear t f Int
, tPrice :: !Double , tPrice :: Wear t f Double
} deriving (Show, Eq, Ord) } deriving (Generic)
type TradeNotification = TradeNotificationB Bare Identity
deriving instance FunctorB (TradeNotificationB Covered)
deriving instance TraversableB (TradeNotificationB Covered)
deriving instance ConstraintsB (TradeNotificationB Covered)
deriving instance Show TradeNotification
deriving instance Eq TradeNotification
deriving instance Ord TradeNotification
deriving instance BareB TradeNotificationB
newtype ResponseTrades = newtype ResponseTrades =
ResponseTrades [TradeNotification] ResponseTrades [TradeNotification]
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC ResponseTrades where instance TransaqResponseC Element ResponseTrades where
fromXml root = do fromXml root = do
quotes <- mapM parseTrade $ elChildren root quotes <- mapM parseTrade $ elChildren root
pure . ResponseTrades . catMaybes $ quotes pure . ResponseTrades . catMaybes $ quotes
@ -884,22 +1036,32 @@ instance TransaqResponseC ResponseTrades where
!tComission <- childContent "comission" tag >>= readMaybe !tComission <- childContent "comission" tag >>= readMaybe
!tQuantity <- childContent "quantity" tag >>= readMaybe !tQuantity <- childContent "quantity" tag >>= readMaybe
!tPrice <- childContent "price" tag >>= readMaybe !tPrice <- childContent "price" tag >>= readMaybe
pure . Just $ TradeNotification {..} pure . Just $ (TradeNotification {..} :: TradeNotification)
data Tick = data TickB t f =
Tick Tick
{ {
secId :: !Int secId :: Wear t f Int
, tradeNo :: !Int64 , tradeNo :: Wear t f Int64
, timestamp :: !UTCTime , timestamp :: Wear t f UTCTime
, price :: !Double , price :: Wear t f Double
, quantity :: !Int , quantity :: Wear t f Int
, period :: !TradingPeriod , period :: Wear t f TradingPeriod
, buySell :: !TradeDirection , buySell :: Wear t f TradeDirection
, openInterest :: !Int , openInterest :: Wear t f Int
, board :: !T.Text , board :: Wear t f T.Text
, secCode :: !T.Text , secCode :: Wear t f T.Text
} deriving (Show, Eq, Ord) } deriving (Generic)
type Tick = TickB Bare Identity
deriving instance FunctorB (TickB Covered)
deriving instance TraversableB (TickB Covered)
deriving instance ConstraintsB (TickB Covered)
deriving instance Show Tick
deriving instance Eq Tick
deriving instance Ord Tick
deriving instance BareB TickB
newtype ResponseTicks = newtype ResponseTicks =
ResponseTicks [Tick] ResponseTicks [Tick]
@ -921,7 +1083,8 @@ data TransaqResponse =
| TransaqResponseTrades ResponseTrades | TransaqResponseTrades ResponseTrades
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
instance TransaqResponseC TransaqResponse where
instance TransaqResponseC Element TransaqResponse where
fromXml root = case qName . elName $ root of fromXml root = case qName . elName $ root of
"result" -> TransaqResponseResult <$> fromXml root "result" -> TransaqResponseResult <$> fromXml root
"error" -> TransaqResponseResult <$> fromXml root "error" -> TransaqResponseResult <$> fromXml root

7
test/Spec.hs

@ -1,10 +1,15 @@
import Debug.EventCounters (initEventCounters)
import System.Metrics (newStore)
import Test.Tasty import Test.Tasty
import qualified Test.FSM import qualified Test.FSM
import qualified Test.TickTable import qualified Test.TickTable
main :: IO () main :: IO ()
main = defaultMain $ testGroup "Tests" [unitTests] main = do
store <- newStore
initEventCounters store
defaultMain $ testGroup "Tests" [unitTests]
unitTests :: TestTree unitTests :: TestTree
unitTests = testGroup "Unit Tests" unitTests = testGroup "Unit Tests"

12
test/Test/Transaq.hs

@ -0,0 +1,12 @@
module Test.Transaq
(
unitTests
) where
unitTests :: TestTree
unitTests = testGroup "Parsing"
[
test
]

4
transaq-connector.cabal

@ -63,6 +63,8 @@ executable transaq-connector
, ekg-core , ekg-core
, slave-thread , slave-thread
, th-printf , th-printf
, barbies
, xeno
extra-lib-dirs: lib extra-lib-dirs: lib
ghc-options: -Wall ghc-options: -Wall
-Wcompat -Wcompat
@ -124,6 +126,8 @@ test-suite transaq-connector-test
, ekg-statsd , ekg-statsd
, ekg-core , ekg-core
, slave-thread , slave-thread
, xeno
, barbies
default-extensions: OverloadedStrings default-extensions: OverloadedStrings
, MultiWayIf , MultiWayIf
, MultiParamTypeClasses , MultiParamTypeClasses

Loading…
Cancel
Save