Browse Source

Test: build

master
Denis Tereshkin 3 years ago
parent
commit
dc6702765f
  1. 4
      robocom-zero.cabal
  2. 2
      src/ATrade/Driver/Junction/QuoteThread.hs
  3. 13
      test/Test/BarAggregator.hs
  4. 19
      test/Test/Driver/Junction/QuoteThread.hs

4
robocom-zero.cabal

@ -99,6 +99,8 @@ test-suite robots-test @@ -99,6 +99,8 @@ test-suite robots-test
, tasty-golden
, tasty-hedgehog
, tasty-hspec
, tasty-quickcheck
, tasty-smallcheck
, quickcheck-text
, quickcheck-instances
, containers
@ -107,6 +109,8 @@ test-suite robots-test @@ -107,6 +109,8 @@ test-suite robots-test
, zeromq4-haskell-zap
, BoundedChan
, mtl
, co-log-core
, co-log
ghc-options: -threaded -rtsopts -with-rtsopts=-N
default-language: Haskell2010
other-modules: Test.RoboCom.Indicators

2
src/ATrade/Driver/Junction/QuoteThread.hs

@ -93,7 +93,7 @@ data QuoteThreadEnv = @@ -93,7 +93,7 @@ data QuoteThreadEnv =
startQuoteThread :: (MonadIO m,
MonadIO m1,
WithLog DownloaderEnv Message m1,
WithLog env Message m1,
HistoryProvider m1,
TickerInfoProvider m1) =>
IORef Bars ->

13
test/Test/BarAggregator.hs

@ -33,11 +33,10 @@ unitTests = testGroup "BarAggregator" [ @@ -33,11 +33,10 @@ unitTests = testGroup "BarAggregator" [
]
properties = testGroup "BarAggregator" [
prop_allTicksInOneBar,
prop_ticksInTwoBars
prop_allTicksInOneBar
]
secParams = InstrumentParameters 1 0.01
secParams = InstrumentParameters "TEST_TICKER" 1 0.01
testUnknownBarSeries :: TestTree
testUnknownBarSeries = testCase "Tick with unknown ticker id" $ do
@ -125,10 +124,10 @@ prop_allTicksInOneBar = testProperty "All ticks in one bar" $ property $ do @@ -125,10 +124,10 @@ prop_allTicksInOneBar = testProperty "All ticks in one bar" $ property $ do
where
genTick :: T.Text -> UTCTime -> Int -> Gen Tick
genTick tickerId base tf = do
difftime <- fromRational . toRational . picosecondsToDiffTime <$> choose (0, truncate 1e12 * fromIntegral tf)
val <- arbitrary
vol <- arbitrary `suchThat` (> 0)
return $ Tick tickerId LastTradePrice (difftime `addUTCTime` baseTime) val vol
difftime <- fromRational . toRational . picosecondsToDiffTime <$> Gen.integral (Range.linear 0 (truncate 1e12 * fromIntegral tf))
val <- fromIntegral <$> Gen.int (Range.linear 1 1000000)
vol <- Gen.integral (Range.linear 1 1000000)
return $ Tick tickerId LastTradePrice (difftime `addUTCTime` baseTime) (fromDouble $ val / 1000) vol
mkAggregator tickerId tf = mkAggregatorFromBars (M.singleton tickerId (BarSeries tickerId (BarTimeframe tf) [] secParams)) [(0, 86400)]
currentBar tickerId agg = headMay =<< (bsBars <$> M.lookup tickerId (bars agg))

19
test/Test/Driver/Junction/QuoteThread.hs

@ -1,5 +1,6 @@ @@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
@ -16,6 +17,7 @@ import Test.Tasty.SmallCheck as SC @@ -16,6 +17,7 @@ import Test.Tasty.SmallCheck as SC
import ATrade.Driver.Junction.QuoteThread (addSubscription,
startQuoteThread,
stopQuoteThread)
import ATrade.Logging (Message)
import ATrade.Quotes.HistoryProvider (HistoryProvider (..))
import ATrade.Quotes.TickerInfoProvider (TickerInfoProvider (..))
import ATrade.QuoteSource.Client (QuoteData (QDBar))
@ -26,23 +28,21 @@ import ATrade.RoboCom.Types (BarSeries (bsBars), @@ -26,23 +28,21 @@ import ATrade.RoboCom.Types (BarSeries (bsBars),
BarSeriesId (BarSeriesId),
InstrumentParameters (InstrumentParameters))
import ATrade.Types
import Colog.Core (LogAction (..))
import Colog.Core.Class (HasLog (..))
import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.BoundedChan (newBoundedChan, readChan,
writeChan)
import Control.Exception (bracket)
import Control.Monad (forever)
import Control.Monad.Reader
import Data.IORef (newIORef, readIORef)
import Data.IORef (IORef, newIORef, readIORef)
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import Data.Time (UTCTime (UTCTime),
fromGregorian)
import System.IO (BufferMode (LineBuffering),
hSetBuffering, stderr)
import System.Log.Formatter
import System.Log.Handler (setFormatter)
import System.Log.Handler.Simple
import System.Log.Logger
import System.ZMQ4 (withContext)
import Test.Mock.HistoryProvider (MockHistoryProvider,
mkMockHistoryProvider,
@ -70,13 +70,16 @@ instance TickerInfoProvider TestM where @@ -70,13 +70,16 @@ instance TickerInfoProvider TestM where
tip <- asks tickerInfoProvider
liftIO $ mockGetInstrumentParameters tip tickers
instance HasLog TestEnv Message TestM where
getLogAction env = LogAction $ \msg -> return ()
qsEndpoint = "inproc://qs"
mockHistoryProvider = mkMockHistoryProvider $ M.fromList [(BarSeriesId "FOO" (BarTimeframe 3600), bars)]
where
bars = []
mockTickerInfoProvider = mkMockTickerInfoProvider $ M.fromList [("FOO", InstrumentParameters 10 0.1)]
mockTickerInfoProvider = mkMockTickerInfoProvider $ M.fromList [("FOO", InstrumentParameters "FOO" 10 0.1)]
unitTests = testGroup "Driver.Junction.QuoteThread" [
testSubscription
@ -85,12 +88,14 @@ unitTests = testGroup "Driver.Junction.QuoteThread" [ @@ -85,12 +88,14 @@ unitTests = testGroup "Driver.Junction.QuoteThread" [
testSubscription :: TestTree
testSubscription = testCase "Subscription" $ withContext $ \ctx -> do
barsRef <- newIORef M.empty
tiRef <- newIORef M.empty
serverChan <- newBoundedChan 2000
let clientSecurityParams = defaultClientSecurityParams
bracket
(startQuoteSourceServer serverChan ctx qsEndpoint defaultServerSecurityParams)
stopQuoteSourceServer $ \_ ->
bracket
(startQuoteThread barsRef ctx qsEndpoint Nothing Nothing (`runReaderT` (TestEnv mockHistoryProvider mockTickerInfoProvider)))
(startQuoteThread barsRef tiRef ctx qsEndpoint clientSecurityParams (`runReaderT` (TestEnv mockHistoryProvider mockTickerInfoProvider)) (LogAction $ \_ -> return ()))
stopQuoteThread $ \qt -> do
chan <- newBoundedChan 2000

Loading…
Cancel
Save