|
|
|
@ -6,7 +6,9 @@ module ATrade.Types ( |
|
|
|
Bar(..), |
|
|
|
Bar(..), |
|
|
|
DataType(..), |
|
|
|
DataType(..), |
|
|
|
serializeTick, |
|
|
|
serializeTick, |
|
|
|
|
|
|
|
serializeTickBody, |
|
|
|
deserializeTick, |
|
|
|
deserializeTick, |
|
|
|
|
|
|
|
deserializeTickBody, |
|
|
|
SignalId(..), |
|
|
|
SignalId(..), |
|
|
|
OrderPrice(..), |
|
|
|
OrderPrice(..), |
|
|
|
Operation(..), |
|
|
|
Operation(..), |
|
|
|
@ -32,6 +34,7 @@ import Data.Ratio |
|
|
|
import Data.Text as T |
|
|
|
import Data.Text as T |
|
|
|
import Data.Text.Encoding as E |
|
|
|
import Data.Text.Encoding as E |
|
|
|
import Data.Time.Clock |
|
|
|
import Data.Time.Clock |
|
|
|
|
|
|
|
import Data.Time.Clock.POSIX |
|
|
|
import Data.Word |
|
|
|
import Data.Word |
|
|
|
|
|
|
|
|
|
|
|
type TickerId = T.Text |
|
|
|
type TickerId = T.Text |
|
|
|
@ -82,11 +85,11 @@ data Tick = Tick { |
|
|
|
volume :: !Integer |
|
|
|
volume :: !Integer |
|
|
|
} deriving (Show, Eq) |
|
|
|
} deriving (Show, Eq) |
|
|
|
|
|
|
|
|
|
|
|
serializeTick :: Tick -> [ByteString] |
|
|
|
serializeTickHeader :: Tick -> ByteString |
|
|
|
serializeTick tick = header : [rawdata] |
|
|
|
serializeTickHeader tick = B.fromStrict . E.encodeUtf8 $ security tick |
|
|
|
where |
|
|
|
|
|
|
|
header = B.fromStrict . E.encodeUtf8 $ security tick |
|
|
|
serializeTickBody :: Tick -> ByteString |
|
|
|
rawdata = toLazyByteString $ mconcat [ |
|
|
|
serializeTickBody tick = toLazyByteString $ mconcat [ |
|
|
|
putWord32le 1, |
|
|
|
putWord32le 1, |
|
|
|
putWord64le $ fromIntegral . toSeconds' . timestamp $ tick, |
|
|
|
putWord64le $ fromIntegral . toSeconds' . timestamp $ tick, |
|
|
|
putWord32le $ fromIntegral . fracSeconds . timestamp $ tick, |
|
|
|
putWord32le $ fromIntegral . fracSeconds . timestamp $ tick, |
|
|
|
@ -94,22 +97,18 @@ serializeTick tick = header : [rawdata] |
|
|
|
putWord64le $ truncate . value $ tick, |
|
|
|
putWord64le $ truncate . value $ tick, |
|
|
|
putWord32le $ truncate . (*. 1000000000) . fractionalPart $ value tick, |
|
|
|
putWord32le $ truncate . (*. 1000000000) . fractionalPart $ value tick, |
|
|
|
putWord32le $ fromIntegral $ volume tick ] |
|
|
|
putWord32le $ fromIntegral $ volume tick ] |
|
|
|
floorPart :: (RealFrac a) => a -> a |
|
|
|
where |
|
|
|
floorPart x = x - fromIntegral (floor x) |
|
|
|
|
|
|
|
fractionalPart :: (RealFrac a) => a -> a |
|
|
|
fractionalPart :: (RealFrac a) => a -> a |
|
|
|
fractionalPart x = x - fromIntegral (truncate x) |
|
|
|
fractionalPart x = x - fromIntegral (truncate x) |
|
|
|
toSeconds' t = floor $ diffUTCTime t epoch |
|
|
|
toSeconds' = floor . utcTimeToPOSIXSeconds |
|
|
|
fracSeconds t = (truncate $ (* 1000000000000) $ diffUTCTime t epoch) `mod` 1000000000000 `div` 1000000 |
|
|
|
fracSeconds t = (truncate $ (* 1000000000000) $ utcTimeToPOSIXSeconds t) `mod` 1000000000000 `div` 1000000 |
|
|
|
epoch = fromGregorian 1970 1 1 0 0 0 |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
deserializeTick :: [ByteString] -> Maybe Tick |
|
|
|
serializeTick :: Tick -> [ByteString] |
|
|
|
deserializeTick (header:rawData:_) = case runGetOrFail parseTick rawData of |
|
|
|
serializeTick tick = serializeTickHeader tick : [serializeTickBody tick] |
|
|
|
Left (_, _, _) -> Nothing |
|
|
|
|
|
|
|
Right (_, _, tick) -> Just $ tick { security = E.decodeUtf8 . B.toStrict $ header } |
|
|
|
parseTick :: Get Tick |
|
|
|
where |
|
|
|
parseTick = do |
|
|
|
parseTick :: Get Tick |
|
|
|
|
|
|
|
parseTick = do |
|
|
|
|
|
|
|
packetType <- fromEnum <$> getWord32le |
|
|
|
packetType <- fromEnum <$> getWord32le |
|
|
|
when (packetType /= 1) $ fail "Expected packettype == 1" |
|
|
|
when (packetType /= 1) $ fail "Expected packettype == 1" |
|
|
|
tsec <- getWord64le |
|
|
|
tsec <- getWord64le |
|
|
|
@ -123,7 +122,7 @@ deserializeTick (header:rawData:_) = case runGetOrFail parseTick rawData of |
|
|
|
timestamp = makeTimestamp tsec tusec, |
|
|
|
timestamp = makeTimestamp tsec tusec, |
|
|
|
value = makeValue intpart nanopart, |
|
|
|
value = makeValue intpart nanopart, |
|
|
|
volume = volume } |
|
|
|
volume = volume } |
|
|
|
|
|
|
|
where |
|
|
|
makeTimestamp :: Word64 -> Word32 -> UTCTime |
|
|
|
makeTimestamp :: Word64 -> Word32 -> UTCTime |
|
|
|
makeTimestamp sec usec = addUTCTime (fromRational $ toInteger usec % 1000000) (fromSeconds . toInteger $ sec) |
|
|
|
makeTimestamp sec usec = addUTCTime (fromRational $ toInteger usec % 1000000) (fromSeconds . toInteger $ sec) |
|
|
|
|
|
|
|
|
|
|
|
@ -135,8 +134,18 @@ deserializeTick (header:rawData:_) = case runGetOrFail parseTick rawData of |
|
|
|
convertedIntPart = realFracToDecimal 10 (fromIntegral intpart) |
|
|
|
convertedIntPart = realFracToDecimal 10 (fromIntegral intpart) |
|
|
|
r = toInteger nanopart % 1000000000 |
|
|
|
r = toInteger nanopart % 1000000000 |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
deserializeTick :: [ByteString] -> Maybe Tick |
|
|
|
|
|
|
|
deserializeTick (header:rawData:_) = case runGetOrFail parseTick rawData of |
|
|
|
|
|
|
|
Left (_, _, _) -> Nothing |
|
|
|
|
|
|
|
Right (_, _, tick) -> Just $ tick { security = E.decodeUtf8 . B.toStrict $ header } |
|
|
|
|
|
|
|
|
|
|
|
deserializeTick _ = Nothing |
|
|
|
deserializeTick _ = Nothing |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
deserializeTickBody :: ByteString -> (ByteString, Maybe Tick) |
|
|
|
|
|
|
|
deserializeTickBody bs = case runGetOrFail parseTick bs of |
|
|
|
|
|
|
|
Left (rest, _, _) -> (rest, Nothing) |
|
|
|
|
|
|
|
Right (rest, _, tick) -> (rest, Just tick) |
|
|
|
|
|
|
|
|
|
|
|
data Bar = Bar { |
|
|
|
data Bar = Bar { |
|
|
|
barSecurity :: !TickerId, |
|
|
|
barSecurity :: !TickerId, |
|
|
|
barTimestamp :: !UTCTime, |
|
|
|
barTimestamp :: !UTCTime, |
|
|
|
|