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.
34 lines
1.0 KiB
34 lines
1.0 KiB
{-# LANGUAGE OverloadedStrings #-} |
|
|
|
module Test.TickTable |
|
( |
|
unitTests |
|
) where |
|
|
|
import ATrade.Price (fromDouble) |
|
import ATrade.Types (DataType (..), Tick (..)) |
|
import Control.Monad.IO.Class (MonadIO (..)) |
|
import Data.Time (fromGregorian) |
|
import Data.Time.Clock (UTCTime (..)) |
|
import Test.Tasty |
|
import Test.Tasty.HUnit (testCase, (@?=)) |
|
import TickTable (insertTick, lookupTick, newTickTable) |
|
|
|
unitTests :: TestTree |
|
unitTests = testGroup "TickTable" |
|
[ testInsertAndLookup ] |
|
|
|
testInsertAndLookup = testCase "Insert and lookup" $ do |
|
tt <- liftIO newTickTable |
|
insertTick tt testTick |
|
maybeTick <- lookupTick tt (security testTick) (datatype testTick) |
|
maybeTick @?= Just testTick |
|
where |
|
testTick = Tick |
|
{ |
|
security = "TEST_TICK" |
|
, datatype = LastTradePrice |
|
, value = fromDouble 12.01 |
|
, volume = 45 |
|
, timestamp = UTCTime (fromGregorian 2000 1 1) 0 |
|
}
|
|
|