ATrade core infrastructure
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.

47 lines
1.5 KiB

{-# LANGUAGE OverloadedStrings #-}
module TestQuoteSourceServer (
unitTests
) where
import Test.Tasty
import Test.Tasty.HUnit
import ATrade.Types
import qualified Data.ByteString.Lazy as BL
import ATrade.QuoteSource.Server
9 years ago
import Control.Concurrent.BoundedChan
import Control.Exception
import System.ZMQ4
import Data.Time.Clock
import Data.Time.Calendar
unitTests :: TestTree
unitTests = testGroup "QuoteSource.Server" [testStartStop, testTickStream]
testStartStop :: TestTree
testStartStop = testCase "QuoteSource Server starts and stops" $ withContext (\ctx -> do
9 years ago
chan <- newBoundedChan 1000
qss <- startQuoteSourceServer chan ctx "inproc://quotesource-server" Nothing
stopQuoteSourceServer qss)
testTickStream :: TestTree
testTickStream = testCase "QuoteSource Server sends ticks" $ withContext (\ctx -> do
9 years ago
chan <- newBoundedChan 1000
bracket (startQuoteSourceServer chan ctx "inproc://quotesource-server" Nothing) stopQuoteSourceServer (\_ ->
withSocket ctx Sub (\s -> do
connect s "inproc://quotesource-server"
subscribe s "FOOBAR"
let tick = Tick {
security = "FOOBAR",
datatype = LastTradePrice,
timestamp = UTCTime (fromGregorian 2016 9 27) 16000,
value = 1000,
volume = 1}
9 years ago
writeChan chan (QSSTick tick)
packet <- fmap BL.fromStrict <$> receiveMulti s
case deserializeTick packet of
Just recvdTick -> tick @=? recvdTick
Nothing -> assertFailure "Unable to deserialize tick")))