9 changed files with 265 additions and 103 deletions
@ -0,0 +1,43 @@
@@ -0,0 +1,43 @@
|
||||
|
||||
module Linux.TXML |
||||
( |
||||
initialize |
||||
, uninitialize |
||||
, sendCommand |
||||
, setCallback |
||||
, freeCallback |
||||
, Callback |
||||
, LogLevel(..) |
||||
) where |
||||
|
||||
import qualified Data.ByteString.Char8 as BS |
||||
import qualified Data.Text as T |
||||
import Data.Text.Encoding |
||||
import Data.Text.Encoding.Error |
||||
import Foreign.C.String |
||||
import Foreign.C.Types |
||||
import Foreign.Ptr |
||||
|
||||
data LogLevel = |
||||
Debug |
||||
| Info |
||||
| Warning |
||||
deriving (Show, Eq, Ord) |
||||
|
||||
newtype Callback = Callback { unCallback :: FunPtr (CString -> IO CBool)} |
||||
|
||||
initialize :: FilePath -> LogLevel -> IO (Either T.Text ()) |
||||
initialize fp loglevel = return (Right ()) |
||||
|
||||
uninitialize :: IO (Either T.Text ()) |
||||
uninitialize = return (Right ()) |
||||
|
||||
sendCommand :: T.Text -> IO (Either T.Text ()) |
||||
sendCommand cmdData = return (Right ()) |
||||
|
||||
setCallback :: (T.Text -> IO Bool) -> IO (Maybe Callback) |
||||
setCallback callback = return Nothing |
||||
|
||||
freeCallback :: Callback -> IO () |
||||
freeCallback = freeHaskellFunPtr . unCallback |
||||
|
||||
@ -0,0 +1,40 @@
@@ -0,0 +1,40 @@
|
||||
{-# LANGUAGE RecordWildCards #-} |
||||
|
||||
module TickTable |
||||
( |
||||
TickTable |
||||
, newTickTable |
||||
, insertTick |
||||
, lookupTick |
||||
) where |
||||
|
||||
import ATrade.Types (DataType, |
||||
Tick (datatype, security), |
||||
TickerId) |
||||
import Control.Concurrent.STM.TVar (TVar, modifyTVar', newTVarIO, |
||||
readTVarIO) |
||||
import Control.Monad.IO.Class (MonadIO (..)) |
||||
import Control.Monad.STM (atomically) |
||||
import qualified Data.Map.Strict as M |
||||
|
||||
data TickKey = TickKey TickerId DataType |
||||
deriving (Show, Ord, Eq) |
||||
|
||||
newtype TickTable = |
||||
TickTable |
||||
{ |
||||
ttMap :: TVar (M.Map TickKey Tick) |
||||
} |
||||
|
||||
newTickTable :: (MonadIO m) => m TickTable |
||||
newTickTable = do |
||||
ttMap <- liftIO $ newTVarIO M.empty |
||||
pure TickTable{..} |
||||
|
||||
insertTick :: (MonadIO m) => TickTable -> Tick -> m () |
||||
insertTick tickTable tick = |
||||
liftIO . atomically $ modifyTVar' (ttMap tickTable) (M.insert (TickKey (security tick) (datatype tick)) tick) |
||||
|
||||
lookupTick :: (MonadIO m) => TickTable -> TickerId -> DataType -> m (Maybe Tick) |
||||
lookupTick tickTable tickerId datatype = |
||||
M.lookup (TickKey tickerId datatype) <$> liftIO (readTVarIO (ttMap tickTable)) |
||||
@ -0,0 +1,100 @@
@@ -0,0 +1,100 @@
|
||||
|
||||
module Win32.TXML |
||||
( |
||||
initialize |
||||
, uninitialize |
||||
, sendCommand |
||||
, setCallback |
||||
, freeCallback |
||||
, Callback |
||||
, LogLevel(..) |
||||
) where |
||||
|
||||
import qualified Data.ByteString.Char8 as BS |
||||
import qualified Data.Text as T |
||||
import Data.Text.Encoding |
||||
import Data.Text.Encoding.Error |
||||
import Foreign.C.String |
||||
import Foreign.C.Types |
||||
import Foreign.Ptr |
||||
|
||||
foreign import ccall "Initialize" c_Initialize :: CString -> CInt -> IO CString |
||||
foreign import ccall "UnInitialize" c_UnInitialize :: IO CString |
||||
foreign import ccall "SendCommand" c_SendCommand :: CString -> IO CString |
||||
foreign import ccall "SetCallback" c_SetCallback :: |
||||
FunPtr (CString -> IO CBool) -> IO CBool |
||||
foreign import ccall "FreeMemory" c_FreeMemory :: CString -> IO CBool |
||||
|
||||
foreign import ccall "wrapper" createCallbackPtr :: |
||||
(CString -> IO CBool) -> IO (FunPtr (CString -> IO CBool)) |
||||
|
||||
data LogLevel = |
||||
Debug |
||||
| Info |
||||
| Warning |
||||
deriving (Show, Eq, Ord) |
||||
|
||||
newtype Callback = Callback { unCallback :: FunPtr (CString -> IO CBool)} |
||||
|
||||
logLevelToInt :: LogLevel -> CInt |
||||
logLevelToInt Debug = 3 |
||||
logLevelToInt Info = 2 |
||||
logLevelToInt Warning = 1 |
||||
|
||||
strErrorStringToResult :: CString -> IO (Either T.Text ()) |
||||
strErrorStringToResult str = |
||||
if nullPtr /= str |
||||
then do |
||||
packed <- BS.packCString str |
||||
let result = decodeUtf8With (replace '?') $ packed |
||||
_ <- c_FreeMemory str |
||||
pure $ Left result |
||||
else |
||||
pure $ Right () |
||||
|
||||
rawStringToResult :: CString -> IO (Either T.Text ()) |
||||
rawStringToResult str = |
||||
if nullPtr /= str |
||||
then do |
||||
packed <- BS.packCString str |
||||
let result = decodeUtf8With (replace '?') $ packed |
||||
_ <- c_FreeMemory str |
||||
if "<result success=\"true\"/>" `T.isPrefixOf` result |
||||
then pure $ Right () |
||||
else pure $ Left result |
||||
else |
||||
pure $ Left "" |
||||
|
||||
initialize :: FilePath -> LogLevel -> IO (Either T.Text ()) |
||||
initialize fp loglevel = |
||||
BS.useAsCString (encodeUtf8 . T.pack $ fp) $ \fpcstr -> |
||||
c_Initialize fpcstr (logLevelToInt loglevel) >>= strErrorStringToResult |
||||
|
||||
uninitialize :: IO (Either T.Text ()) |
||||
uninitialize = c_UnInitialize >>= rawStringToResult |
||||
|
||||
sendCommand :: T.Text -> IO (Either T.Text ()) |
||||
sendCommand cmdData = do |
||||
BS.useAsCString (encodeUtf8 cmdData) $ \fpcstr -> |
||||
c_SendCommand fpcstr >>= rawStringToResult |
||||
|
||||
setCallback :: (T.Text -> IO Bool) -> IO (Maybe Callback) |
||||
setCallback callback = do |
||||
wrappedCallback <- createCallbackPtr (\x -> do |
||||
packed <- BS.packCString x |
||||
boolToCBool <$> (callback $ |
||||
decodeUtf8With (replace '?') |
||||
packed)) |
||||
ret <- c_SetCallback wrappedCallback |
||||
if ret /= 0 |
||||
then return . Just . Callback $ wrappedCallback |
||||
else do |
||||
freeHaskellFunPtr wrappedCallback |
||||
return Nothing |
||||
where |
||||
boolToCBool False = 0 |
||||
boolToCBool True = 1 |
||||
|
||||
freeCallback :: Callback -> IO () |
||||
freeCallback = freeHaskellFunPtr . unCallback |
||||
|
||||
@ -0,0 +1,9 @@
@@ -0,0 +1,9 @@
|
||||
|
||||
import Test.Tasty |
||||
|
||||
main :: IO () |
||||
main = defaultMain $ testGroup "Tests" [unitTests] |
||||
|
||||
unitTests :: TestTree |
||||
unitTests = testGroup "Unit Tests" |
||||
[ Test.RoboCom.Indicators.unitTests ] |
||||
@ -0,0 +1,10 @@
@@ -0,0 +1,10 @@
|
||||
import Test.Tasty |
||||
|
||||
import qualified Test.TickTable |
||||
|
||||
main :: IO () |
||||
main = defaultMain $ testGroup "Tests" [unitTests] |
||||
|
||||
unitTests :: TestTree |
||||
unitTests = testGroup "Unit Tests" |
||||
[Test.TickTable.unitTests ] |
||||
@ -0,0 +1,34 @@
@@ -0,0 +1,34 @@
|
||||
{-# 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 |
||||
} |
||||
Loading…
Reference in new issue