diff --git a/src/Transaq.hs b/src/Transaq.hs index 89ede1a..48f56d0 100644 --- a/src/Transaq.hs +++ b/src/Transaq.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE RecordWildCards #-} @@ -90,31 +91,31 @@ parseTimestamp = hush . parseOnly parser where parser = parseWithDate <|> (UTCTime epoch <$> parseTime) parseWithDate = do - date <- parseDate + !date <- parseDate skipSpace - time <- parseTime + !time <- parseTime pure $ UTCTime date time parseDate = do - day <- decimal + !day <- decimal void $ char '.' - month <- decimal + !month <- decimal void $ char '.' - year <- decimal + !year <- decimal pure $ fromGregorian year month day parseTime = do - hour <- (decimal :: Parser Int) + !hour <- (decimal :: Parser Int) void $ char ':' - minute <- decimal + !minute <- decimal void $ char ':' - second <- decimal + !second <- decimal msecs <- many' $ do void $ char '.' (decimal :: Parser Int) - let secofday = hour * 3600 + minute * 60 + second + let !secofday = hour * 3600 + minute * 60 + second case msecs of - [ms] -> pure $ fromIntegral secofday + fromIntegral ms / 1000.0 - _ -> pure $ fromIntegral secofday + [!ms] -> pure $ fromIntegral secofday + fromIntegral ms / 1000.0 + _ -> pure $ fromIntegral secofday epoch = fromGregorian 1970 1 1 @@ -127,21 +128,21 @@ class TransaqResponseC t where data CommandConnect = CommandConnect { - login :: T.Text, - password :: T.Text, - host :: T.Text, - port :: Int, - language :: Language, - autopos :: Bool, - micexRegisters :: Bool, - milliseconds :: Bool, - utcTime :: Bool, + login :: !T.Text, + password :: !T.Text, + host :: !T.Text, + port :: !Int, + language :: !Language, + autopos :: !Bool, + micexRegisters :: !Bool, + milliseconds :: !Bool, + utcTime :: !Bool, proxy :: (), -- not supported - rqDelay :: Maybe Int, - sessionTimeout :: Maybe Int, - requestTimeout :: Maybe Int, - pushULimits :: Maybe Int, - pushPosEquity :: Maybe Int + rqDelay :: !(Maybe Int), + sessionTimeout :: !(Maybe Int), + requestTimeout :: !(Maybe Int), + pushULimits :: !(Maybe Int), + pushPosEquity :: !(Maybe Int) } deriving (Show, Eq, Ord) instance Node CommandConnect where @@ -177,8 +178,8 @@ instance TransaqCommand CommandDisconnect where data SecurityId = SecurityId { - board :: T.Text - , seccode :: T.Text + board :: !T.Text + , seccode :: !T.Text } deriving (Show, Eq, Ord) data CommandServerStatus = CommandServerStatus @@ -197,9 +198,9 @@ instance Node SecurityId where data CommandSubscribe = CommandSubscribe { - alltrades :: [SecurityId] - , quotations :: [SecurityId] - , quotes :: [SecurityId] + alltrades :: ![SecurityId] + , quotations :: ![SecurityId] + , quotes :: ![SecurityId] } deriving (Show, Eq, Ord) instance TransaqCommand CommandSubscribe where @@ -213,9 +214,9 @@ instance TransaqCommand CommandSubscribe where data CommandUnsubscribe = CommandUnsubscribe { - alltrades :: [SecurityId] - , quotations :: [SecurityId] - , quotes :: [SecurityId] + alltrades :: ![SecurityId] + , quotations :: ![SecurityId] + , quotes :: ![SecurityId] } deriving (Show, Eq, Ord) instance TransaqCommand CommandUnsubscribe where @@ -229,10 +230,10 @@ instance TransaqCommand CommandUnsubscribe where data CommandGetHistoryData = CommandGetHistoryData { - security :: SecurityId - , periodId :: Int - , count :: Int - , reset :: Bool + security :: !SecurityId + , periodId :: !Int + , count :: !Int + , reset :: !Bool } deriving (Show, Eq, Ord) instance TransaqCommand CommandGetHistoryData where @@ -265,17 +266,17 @@ instance Node UnfilledAction where data CommandNewOrder = CommandNewOrder { - security :: SecurityId - , client :: T.Text - , unionCode :: T.Text - , price :: Double - , quantity :: Int - , buysell :: TradeDirection - , bymarket :: Bool - , brokerRef :: T.Text - , unfilled :: UnfilledAction - , usecredit :: Bool - , nosplit :: Bool + security :: !SecurityId + , client :: !T.Text + , unionCode :: !T.Text + , price :: !Double + , quantity :: !Int + , buysell :: !TradeDirection + , bymarket :: !Bool + , brokerRef :: !T.Text + , unfilled :: !UnfilledAction + , usecredit :: !Bool + , nosplit :: !Bool } deriving (Show, Eq, Ord) instance TransaqCommand CommandNewOrder where @@ -322,8 +323,8 @@ instance TransaqCommand CommandGetSecuritiesInfo where data CommandChangePass = CommandChangePass { - cOldPass :: T.Text - , cNewPass :: T.Text + cOldPass :: !T.Text + , cNewPass :: !T.Text } deriving (Show, Eq) instance TransaqCommand CommandChangePass where @@ -351,13 +352,13 @@ instance TransaqResponseC ResponseResult where data Candle = Candle { - cTimestamp :: UTCTime - , cOpen :: Double - , cHigh :: Double - , cLow :: Double - , cClose :: Double - , cVolume :: Int - , cOpenInterest :: Int + cTimestamp :: !UTCTime + , cOpen :: !Double + , cHigh :: !Double + , cLow :: !Double + , cClose :: !Double + , cVolume :: !Int + , cOpenInterest :: !Int } deriving (Show, Eq, Ord) data ResponseCandlesStatus = @@ -384,11 +385,11 @@ childContent tag el = strContent <$> findChild (uname tag) el instance TransaqResponseC ResponseCandles where fromXml root = do - periodId <- findAttr (uname "period") root >>= readMaybe - status <- findAttr (uname "status") root >>= readMaybe >>= parseStatus - board <- T.pack <$> findAttr (uname "board") root - seccode <- T.pack <$> findAttr (uname "seccode") root - let candles = mapMaybe parseCandle . elChildren $ root + !periodId <- findAttr (uname "period") root >>= readMaybe + !status <- findAttr (uname "status") root >>= readMaybe >>= parseStatus + !board <- T.pack <$> findAttr (uname "board") root + !seccode <- T.pack <$> findAttr (uname "seccode") root + let !candles = mapMaybe parseCandle . elChildren $ root return ResponseCandles { cPeriodId = periodId @@ -406,13 +407,13 @@ instance TransaqResponseC ResponseCandles where 3 -> Just StatusUnavaliable _ -> Nothing parseCandle element = do - timestamp <- findAttr (uname "date") element >>= parseTimestamp . T.pack - open <- findAttr (uname "open") element >>= readMaybe - high <- findAttr (uname "high") element >>= readMaybe - low <- findAttr (uname "low") element >>= readMaybe - close <- findAttr (uname "close") element >>= readMaybe - volume <- findAttr (uname "volume") element >>= readMaybe - let openInterest = fromMaybe 0 $ findAttr (uname "oi") element >>= readMaybe + !timestamp <- findAttr (uname "date") element >>= parseTimestamp . T.pack + !open <- findAttr (uname "open") element >>= readMaybe + !high <- findAttr (uname "high") element >>= readMaybe + !low <- findAttr (uname "low") element >>= readMaybe + !close <- findAttr (uname "close") element >>= readMaybe + !volume <- findAttr (uname "volume") element >>= readMaybe + let !openInterest = fromMaybe 0 $ findAttr (uname "oi") element >>= readMaybe return Candle { cTimestamp = timestamp @@ -433,36 +434,36 @@ data ConnectionState = data ResponseServerStatus = ResponseServerStatus { - serverId :: Maybe Int - , state :: ConnectionState - , recover :: Maybe Bool - , serverTimezone :: Maybe T.Text - , systemVersion :: Maybe Int - , build :: Maybe Int + serverId :: !(Maybe Int) + , state :: !ConnectionState + , recover :: !(Maybe Bool) + , serverTimezone :: !(Maybe T.Text) + , systemVersion :: !(Maybe Int) + , build :: !(Maybe Int) } deriving (Show, Eq, Ord) instance TransaqResponseC ResponseServerStatus where fromXml root = do - let serverId = findAttr (uname "id") root >>= readMaybe - connectedStr <- findAttr (uname "connected") root - state <- case connectedStr of + let !serverId = findAttr (uname "id") root >>= readMaybe + !connectedStr <- findAttr (uname "connected") root + !state <- case connectedStr of "true" -> pure Connected "false" -> pure Disconnected "error" -> pure $ Error (T.pack $ strContent root) _ -> pure Disconnected - let recover = + let !recover = case findAttr (uname "recover") root of Just "true" -> pure True _ -> pure False - let serverTimezone = T.pack <$> findAttr (uname "server_tz") root - let systemVersion = findAttr (uname "sys_ver") root >>= readMaybe - let build = findAttr (uname "build") root >>= readMaybe + let !serverTimezone = T.pack <$> findAttr (uname "server_tz") root + let !systemVersion = findAttr (uname "sys_ver") root >>= readMaybe + let !build = findAttr (uname "build") root >>= readMaybe pure $ ResponseServerStatus {..} data MarketInfo = MarketInfo - { marketId :: Int - , marketName :: T.Text + { marketId :: !Int + , marketName :: !T.Text } deriving (Show, Eq, Ord) newtype ResponseMarkets = ResponseMarkets [MarketInfo] @@ -470,26 +471,26 @@ newtype ResponseMarkets = ResponseMarkets [MarketInfo] instance TransaqResponseC ResponseMarkets where fromXml root = do - markets <- mapM parseMarketInfo $ elChildren root + !markets <- mapM parseMarketInfo $ elChildren root pure . ResponseMarkets . catMaybes $ markets where parseMarketInfo tag = if (qName . elName) tag == "market" then do - marketId <- findAttr (uname "id") tag >>= readMaybe - let marketName = T.pack $ strContent tag + !marketId <- findAttr (uname "id") tag >>= readMaybe + let !marketName = T.pack $ strContent tag pure $ Just $ MarketInfo {..} else pure Nothing data ClientData = ClientData { - cClientId :: T.Text - , cType :: T.Text - , cCurrency :: T.Text - , cMarket :: T.Text - , cUnion :: T.Text - , cForts :: Maybe T.Text + cClientId :: !T.Text + , cType :: !T.Text + , cCurrency :: !T.Text + , cMarket :: !T.Text + , cUnion :: !T.Text + , cForts :: !(Maybe T.Text) } deriving (Show, Eq, Ord) newtype ResponseClient = ResponseClient ClientData @@ -499,21 +500,21 @@ instance TransaqResponseC ResponseClient where fromXml root = do if (qName . elName) root == "client" then do - cClientId <- T.pack <$> findAttr (uname "id") root - cType <- T.pack <$> childContent "type" root - cCurrency <- T.pack <$> childContent "currency" root - cMarket <- T.pack <$> childContent "market" root - cUnion <- T.pack <$> childContent "union" root - let cForts = T.pack <$> childContent "forts_acc" root + !cClientId <- T.pack <$> findAttr (uname "id") root + !cType <- T.pack <$> childContent "type" root + !cCurrency <- T.pack <$> childContent "currency" root + !cMarket <- T.pack <$> childContent "market" root + !cUnion <- T.pack <$> childContent "union" root + let !cForts = T.pack <$> childContent "forts_acc" root Just $ ResponseClient $ ClientData {..} else Nothing data CandleKind = CandleKind { - kCandleKindId :: Int - , kPeriod :: Int - , kName :: T.Text + kCandleKindId :: !Int + , kPeriod :: !Int + , kName :: !T.Text } deriving (Show, Eq, Ord) newtype ResponseCandleKinds = ResponseCandleKinds [CandleKind] @@ -522,35 +523,35 @@ newtype ResponseCandleKinds = ResponseCandleKinds [CandleKind] instance TransaqResponseC ResponseCandleKinds where fromXml root = do - kinds <- mapM parseCandleKind $ elChildren root + !kinds <- mapM parseCandleKind $ elChildren root pure . ResponseCandleKinds . catMaybes $ kinds where parseCandleKind tag = if (qName . elName) tag == "kind" then do - kCandleKindId <- childContent "id" tag >>= readMaybe - kPeriod <- childContent "period" tag >>= readMaybe - kName <- T.pack <$> childContent "name" tag + !kCandleKindId <- childContent "id" tag >>= readMaybe + !kPeriod <- childContent "period" tag >>= readMaybe + !kName <- T.pack <$> childContent "name" tag pure . Just $ CandleKind {..} else pure Nothing data Security = Security { - sSecId :: Int - , sActive :: Bool - , sSeccode :: T.Text - , sInstrClass :: T.Text - , sBoard :: T.Text - , sMarket :: T.Text - , sCurrency :: T.Text - , sShortName :: T.Text - , sDecimals :: Int - , sMinStep :: Double - , sLotSize :: Int - , sLotDivider :: Int - , sPointCost :: Double - , sSecType :: T.Text + sSecId :: !Int + , sActive :: !Bool + , sSeccode :: !T.Text + , sInstrClass :: !T.Text + , sBoard :: !T.Text + , sMarket :: !T.Text + , sCurrency :: !T.Text + , sShortName :: !T.Text + , sDecimals :: !Int + , sMinStep :: !Double + , sLotSize :: !Int + , sLotDivider :: !Int + , sPointCost :: !Double + , sSecType :: !T.Text } deriving (Show, Eq, Ord) newtype ResponseSecurities = @@ -565,20 +566,20 @@ instance TransaqResponseC ResponseSecurities where parseSecurity tag = if (qName . elName) tag == "security" then do - sSecId <- findAttr (uname "secid") tag >>= readMaybe - sActive <- findAttr (uname "active") tag >>= parseBool - sSeccode <- T.pack <$> childContent "seccode" tag - sInstrClass <- T.pack <$> childContent "instrclass" tag - sBoard <- T.pack <$> childContent "board" tag - sMarket <- T.pack <$> childContent "market" tag - let sCurrency = fromMaybe "" $ T.pack <$> childContent "currency" tag - sShortName <- T.pack <$> childContent "shortname" tag - sDecimals <- childContent "decimals" tag >>= readMaybe - sMinStep <- childContent "minstep" tag >>= readMaybe - sLotSize <- childContent "lotsize" tag >>= readMaybe - sLotDivider <- childContent "lotdivider" tag >>= readMaybe - sPointCost <- childContent "point_cost" tag >>= readMaybe - sSecType <- T.pack <$> childContent "sectype" tag + !sSecId <- findAttr (uname "secid") tag >>= readMaybe + !sActive <- findAttr (uname "active") tag >>= parseBool + !sSeccode <- T.pack <$> childContent "seccode" tag + !sInstrClass <- T.pack <$> childContent "instrclass" tag + !sBoard <- T.pack <$> childContent "board" tag + !sMarket <- T.pack <$> childContent "market" tag + let !sCurrency = fromMaybe "" $ T.pack <$> childContent "currency" tag + !sShortName <- T.pack <$> childContent "shortname" tag + !sDecimals <- childContent "decimals" tag >>= readMaybe + !sMinStep <- childContent "minstep" tag >>= readMaybe + !sLotSize <- childContent "lotsize" tag >>= readMaybe + !sLotDivider <- childContent "lotdivider" tag >>= readMaybe + !sPointCost <- childContent "point_cost" tag >>= readMaybe + !sSecType <- T.pack <$> childContent "sectype" tag pure . Just $ Security {..} else pure Nothing @@ -591,15 +592,15 @@ instance TransaqResponseC ResponseSecurities where data ResponseSecInfo = ResponseSecInfo { - secId :: Int - , secName :: T.Text - , secCode :: T.Text - , market :: Int - , pname :: T.Text - , clearingPrice :: Double - , minprice :: Double - , maxprice :: Double - , pointCost :: Double + secId :: !Int + , secName :: !T.Text + , secCode :: !T.Text + , market :: !Int + , pname :: !T.Text + , clearingPrice :: !Double + , minprice :: !Double + , maxprice :: !Double + , pointCost :: !Double } deriving (Show, Eq, Ord) @@ -619,26 +620,26 @@ instance TransaqResponseC ResponseSecInfo where data Quotation = Quotation { - qSecId :: Int - , qBoard :: T.Text - , qSeccode :: T.Text - , qOpen :: Double - , qWaprice :: Double - , qBidDepth :: Int - , qBidDepthT :: Int - , qNumBids :: Int - , qOfferDepth :: Int - , qOfferDepthT :: Int - , qBid :: Double - , qOffer :: Double - , qNumOffers :: Int - , qNumTrades :: Int - , qVolToday :: Int - , qOpenPositions :: Int - , qLastPrice :: Double - , qQuantity :: Int - , qTimestamp :: UTCTime - , qValToday :: Double + qSecId :: !Int + , qBoard :: !T.Text + , qSeccode :: !T.Text + , qOpen :: !Double + , qWaprice :: !Double + , qBidDepth :: !Int + , qBidDepthT :: !Int + , qNumBids :: !Int + , qOfferDepth :: !Int + , qOfferDepthT :: !Int + , qBid :: !Double + , qOffer :: !Double + , qNumOffers :: !Int + , qNumTrades :: !Int + , qVolToday :: !Int + , qOpenPositions :: !Int + , qLastPrice :: !Double + , qQuantity :: !Int + , qTimestamp :: !UTCTime + , qValToday :: !Double } deriving (Show, Eq, Ord) newtype ResponseQuotations = @@ -651,26 +652,26 @@ instance TransaqResponseC ResponseQuotations where pure . ResponseQuotations . catMaybes $ quotations where parseQuotation tag = do - qSecId <- findAttr (uname "secid") tag >>= readMaybe - qBoard <- T.pack <$> childContent "board" tag - qSeccode <- T.pack <$> childContent "seccode" tag - qOpen <- childContent "open" tag >>= readMaybe - qWaprice <- childContent "waprice" tag >>= readMaybe - qBidDepth <- childContent "biddepth" tag >>= readMaybe - qBidDepthT <- childContent "biddeptht" tag >>= readMaybe - qNumBids <- childContent "numbids" tag >>= readMaybe - qBid <- childContent "bid" tag >>= readMaybe - qOfferDepth <- childContent "offerdepth" tag >>= readMaybe - qOfferDepthT <- childContent "offerdeptht" tag >>= readMaybe - qNumOffers <- childContent "numoffers" tag >>= readMaybe - qOffer <- childContent "offer" tag >>= readMaybe - qNumTrades <- childContent "numtrades" tag >>= readMaybe - qVolToday <- childContent "voltoday" tag >>= readMaybe - qOpenPositions <- childContent "openpositions" tag >>= readMaybe - qLastPrice <- childContent "last" tag >>= readMaybe - qQuantity <- childContent "quantity" tag >>= readMaybe - qTimestamp <- childContent "time" tag >>= (parseTimestamp . T.pack) - qValToday <- childContent "valToday" tag >>= readMaybe + !qSecId <- findAttr (uname "secid") tag >>= readMaybe + !qBoard <- T.pack <$> childContent "board" tag + !qSeccode <- T.pack <$> childContent "seccode" tag + !qOpen <- childContent "open" tag >>= readMaybe + !qWaprice <- childContent "waprice" tag >>= readMaybe + !qBidDepth <- childContent "biddepth" tag >>= readMaybe + !qBidDepthT <- childContent "biddeptht" tag >>= readMaybe + !qNumBids <- childContent "numbids" tag >>= readMaybe + !qBid <- childContent "bid" tag >>= readMaybe + !qOfferDepth <- childContent "offerdepth" tag >>= readMaybe + !qOfferDepthT <- childContent "offerdeptht" tag >>= readMaybe + !qNumOffers <- childContent "numoffers" tag >>= readMaybe + !qOffer <- childContent "offer" tag >>= readMaybe + !qNumTrades <- childContent "numtrades" tag >>= readMaybe + !qVolToday <- childContent "voltoday" tag >>= readMaybe + !qOpenPositions <- childContent "openpositions" tag >>= readMaybe + !qLastPrice <- childContent "last" tag >>= readMaybe + !qQuantity <- childContent "quantity" tag >>= readMaybe + !qTimestamp <- childContent "time" tag >>= (parseTimestamp . T.pack) + !qValToday <- childContent "valToday" tag >>= readMaybe pure $ Just Quotation {..} data TradingPeriod = @@ -683,16 +684,16 @@ data TradingPeriod = data AllTradesTrade = AllTradesTrade { - attSecId :: Int - , attSecCode :: T.Text - , attTradeNo :: Int64 - , attTimestamp :: UTCTime - , attBoard :: T.Text - , attPrice :: Double - , attQuantity :: Int - , attBuysell :: TradeDirection - , attOpenInterest :: Int - , attPeriod :: TradingPeriod + attSecId :: !Int + , attSecCode :: !T.Text + , attTradeNo :: !Int64 + , attTimestamp :: !UTCTime + , attBoard :: !T.Text + , attPrice :: !Double + , attQuantity :: !Int + , attBuysell :: !TradeDirection + , attOpenInterest :: !Int + , attPeriod :: !TradingPeriod } deriving (Show, Eq, Ord) newtype ResponseAllTrades = @@ -712,16 +713,16 @@ instance TransaqResponseC ResponseAllTrades where pure . ResponseAllTrades . catMaybes $ alltrades where parseAllTrade tag = do - attSecId <- findAttr (uname "secid") tag >>= readMaybe - attSecCode <- T.pack <$> childContent "seccode" tag - attTradeNo <- childContent "tradeno" tag >>= readMaybe - attTimestamp <- T.pack <$> childContent "time" tag >>= parseTimestamp - attBoard <- T.pack <$> childContent "board" tag - attPrice <- childContent "price" tag >>= readMaybe - attQuantity <- childContent "quantity" tag >>= readMaybe - attBuysell <- T.pack <$> childContent "buysell" tag >>= parseTradeDirection - let attOpenInterest = fromMaybe 0 $ childContent "openinterest" tag >>= readMaybe - let attPeriod = fromMaybe PeriodUnknown $ childContent "period" tag >>= parseTradingPeriod + !attSecId <- findAttr (uname "secid") tag >>= readMaybe + !attSecCode <- T.pack <$> childContent "seccode" tag + !attTradeNo <- childContent "tradeno" tag >>= readMaybe + !attTimestamp <- T.pack <$> childContent "time" tag >>= parseTimestamp + !attBoard <- T.pack <$> childContent "board" tag + !attPrice <- childContent "price" tag >>= readMaybe + !attQuantity <- childContent "quantity" tag >>= readMaybe + !attBuysell <- T.pack <$> childContent "buysell" tag >>= parseTradeDirection + let !attOpenInterest = fromMaybe 0 $ childContent "openinterest" tag >>= readMaybe + let !attPeriod = fromMaybe PeriodUnknown $ childContent "period" tag >>= parseTradingPeriod pure . Just $ AllTradesTrade {..} parseTradingPeriod :: String -> Maybe TradingPeriod @@ -734,14 +735,14 @@ instance TransaqResponseC ResponseAllTrades where data Quote = Quote { - secId :: Int - , board :: T.Text - , secCode :: T.Text - , price :: Double + secId :: !Int + , board :: !T.Text + , secCode :: !T.Text + , price :: !Double , source :: T.Text - , yield :: Int - , buy :: Int - , sell :: Int + , yield :: !Int + , buy :: !Int + , sell :: !Int } deriving (Show, Eq, Ord) newtype ResponseQuotes = @@ -754,14 +755,14 @@ instance TransaqResponseC ResponseQuotes where pure . ResponseQuotes . catMaybes $ quotes where parseQuote tag = do - secId <- findAttr (uname "secid") tag >>= readMaybe - secCode <- T.pack <$> childContent "seccode" tag - board <- T.pack <$> childContent "board" tag - price <- childContent "price" tag >>= readMaybe - source <- T.pack <$> childContent "source" tag - yield <- childContent "yield" tag >>= readMaybe - buy <- childContent "buy" tag >>= readMaybe - sell <- childContent "sell" tag >>= readMaybe + !secId <- findAttr (uname "secid") tag >>= readMaybe + !secCode <- T.pack <$> childContent "seccode" tag + !board <- T.pack <$> childContent "board" tag + !price <- childContent "price" tag >>= readMaybe + !source <- T.pack <$> childContent "source" tag + !yield <- childContent "yield" tag >>= readMaybe + !buy <- childContent "buy" tag >>= readMaybe + !sell <- childContent "sell" tag >>= readMaybe return . Just $ Quote {..} data OrderStatus = @@ -784,21 +785,21 @@ data OrderStatus = data OrderNotification = OrderNotification { - oTransactionId :: Int - , oOrderNo :: Int64 - , oSecId :: Int - , oBoard :: T.Text - , oSecCode :: T.Text - , oClient :: T.Text - , oUnion :: T.Text - , oStatus :: OrderStatus - , oBuysell :: TradeDirection - , oTimestamp :: UTCTime - , oBrokerRef :: T.Text - , oBalance :: Int - , oPrice :: Double - , oQuantity :: Int - , oResult :: T.Text + oTransactionId :: !Int + , oOrderNo :: !Int64 + , oSecId :: !Int + , oBoard :: !T.Text + , oSecCode :: !T.Text + , oClient :: !T.Text + , oUnion :: !T.Text + , oStatus :: !OrderStatus + , oBuysell :: !TradeDirection + , oTimestamp :: !UTCTime + , oBrokerRef :: !T.Text + , oBalance :: !Int + , oPrice :: !Double + , oQuantity :: !Int + , oResult :: !T.Text } deriving (Show, Eq, Ord) newtype ResponseOrders = @@ -811,21 +812,21 @@ instance TransaqResponseC ResponseOrders where pure . ResponseOrders . catMaybes $ quotes where parseOrder tag = do - oTransactionId <- findAttr (uname "transactionid") tag >>= readMaybe - oOrderNo <- childContent "orderno" tag >>= readMaybe - oSecId <- childContent "secid" tag >>= readMaybe - oBoard <- T.pack <$> childContent "board" tag - oSecCode <- T.pack <$> childContent "seccode" tag - oClient <- T.pack <$> childContent "client" tag - oUnion <- T.pack <$> childContent "union" tag - oStatus <- childContent "status" tag >>= parseStatus - oBuysell <- childContent "buysell" tag >>= parseTradeDirection . T.pack - oTimestamp <- childContent "time" tag >>= parseTimestamp . T.pack - oBrokerRef <- T.pack <$> childContent "brokerref" tag - oBalance <- childContent "balance" tag >>= readMaybe - oPrice <- childContent "price" tag >>= readMaybe - oQuantity <- childContent "quantity" tag >>= readMaybe - oResult <- T.pack <$> childContent "result" tag + !oTransactionId <- findAttr (uname "transactionid") tag >>= readMaybe + !oOrderNo <- childContent "orderno" tag >>= readMaybe + !oSecId <- childContent "secid" tag >>= readMaybe + !oBoard <- T.pack <$> childContent "board" tag + !oSecCode <- T.pack <$> childContent "seccode" tag + !oClient <- T.pack <$> childContent "client" tag + !oUnion <- T.pack <$> childContent "union" tag + !oStatus <- childContent "status" tag >>= parseStatus + !oBuysell <- childContent "buysell" tag >>= parseTradeDirection . T.pack + !oTimestamp <- childContent "time" tag >>= parseTimestamp . T.pack + !oBrokerRef <- T.pack <$> childContent "brokerref" tag + !oBalance <- childContent "balance" tag >>= readMaybe + !oPrice <- childContent "price" tag >>= readMaybe + !oQuantity <- childContent "quantity" tag >>= readMaybe + !oResult <- T.pack <$> childContent "result" tag return . Just $ OrderNotification {..} parseStatus "active" = Just OrderActive parseStatus "cancelled" = Just OrderCancelled @@ -846,19 +847,19 @@ instance TransaqResponseC ResponseOrders where data TradeNotification = TradeNotification { - tSecId :: Int - , tTradeNo :: Int64 - , tOrderNo :: Int64 - , tBoard :: T.Text - , tSecCode :: T.Text - , tClient :: T.Text - , tUnion :: T.Text - , tBuysell :: TradeDirection - , tTimestamp :: UTCTime - , tValue :: Double - , tComission :: Double - , tQuantity :: Int - , tPrice :: Double + tSecId :: !Int + , tTradeNo :: !Int64 + , tOrderNo :: !Int64 + , tBoard :: !T.Text + , tSecCode :: !T.Text + , tClient :: !T.Text + , tUnion :: !T.Text + , tBuysell :: !TradeDirection + , tTimestamp :: !UTCTime + , tValue :: !Double + , tComission :: !Double + , tQuantity :: !Int + , tPrice :: !Double } deriving (Show, Eq, Ord) newtype ResponseTrades = @@ -871,34 +872,34 @@ instance TransaqResponseC ResponseTrades where pure . ResponseTrades . catMaybes $ quotes where parseTrade tag = do - tSecId <- childContent "secid" tag >>= readMaybe - tTradeNo <- childContent "tradeno" tag >>= readMaybe - tOrderNo <- childContent "orderno" tag >>= readMaybe - tBoard <- T.pack <$> childContent "board" tag - tSecCode <- T.pack <$> childContent "seccode" tag - tClient <- T.pack <$> childContent "client" tag - tUnion <- T.pack <$> childContent "union" tag - tBuysell <- childContent "buysell" tag >>= parseTradeDirection . T.pack - tTimestamp <- childContent "time" tag >>= parseTimestamp . T.pack - tValue <- childContent "value" tag >>= readMaybe - tComission <- childContent "comission" tag >>= readMaybe - tQuantity <- childContent "quantity" tag >>= readMaybe - tPrice <- childContent "price" tag >>= readMaybe + !tSecId <- childContent "secid" tag >>= readMaybe + !tTradeNo <- childContent "tradeno" tag >>= readMaybe + !tOrderNo <- childContent "orderno" tag >>= readMaybe + !tBoard <- T.pack <$> childContent "board" tag + !tSecCode <- T.pack <$> childContent "seccode" tag + !tClient <- T.pack <$> childContent "client" tag + !tUnion <- T.pack <$> childContent "union" tag + !tBuysell <- childContent "buysell" tag >>= parseTradeDirection . T.pack + !tTimestamp <- childContent "time" tag >>= parseTimestamp . T.pack + !tValue <- childContent "value" tag >>= readMaybe + !tComission <- childContent "comission" tag >>= readMaybe + !tQuantity <- childContent "quantity" tag >>= readMaybe + !tPrice <- childContent "price" tag >>= readMaybe pure . Just $ TradeNotification {..} data Tick = Tick { - secId :: Int - , tradeNo :: Int64 - , timestamp :: UTCTime - , price :: Double - , quantity :: Int - , period :: TradingPeriod - , buySell :: TradeDirection - , openInterest :: Int - , board :: T.Text - , secCode :: T.Text + secId :: !Int + , tradeNo :: !Int64 + , timestamp :: !UTCTime + , price :: !Double + , quantity :: !Int + , period :: !TradingPeriod + , buySell :: !TradeDirection + , openInterest :: !Int + , board :: !T.Text + , secCode :: !T.Text } deriving (Show, Eq, Ord) newtype ResponseTicks =