module Pulsar.Protocol.Frame where
import qualified Data.Binary as B
import qualified Data.ByteString.Lazy.Char8 as CL
import Data.Int ( Int32 )
import Proto.PulsarApi ( BaseCommand
, MessageMetadata
)
frameMaxSize :: Int
frameMaxSize :: Int
frameMaxSize = 5 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1024 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1024
frameMagicNumber :: B.Word16
frameMagicNumber :: Word16
frameMagicNumber = 0x0e01
data Frame = SimpleFrame SimpleCmd | PayloadFrame SimpleCmd PayloadCmd
data SimpleCmd = SimpleCommand
{ SimpleCmd -> Int32
frameTotalSize :: Int32
, SimpleCmd -> Int32
frameCommandSize :: Int32
, SimpleCmd -> ByteString
frameMessage :: CL.ByteString
}
data PayloadCmd = PayloadCommand
{ PayloadCmd -> Word32
frameCheckSum :: B.Word32
, PayloadCmd -> Int32
frameMetadataSize :: Int32
, PayloadCmd -> ByteString
frameMetadata :: CL.ByteString
, PayloadCmd -> ByteString
framePayload :: CL.ByteString
}
newtype Payload = Payload CL.ByteString deriving Int -> Payload -> ShowS
[Payload] -> ShowS
Payload -> String
(Int -> Payload -> ShowS)
-> (Payload -> String) -> ([Payload] -> ShowS) -> Show Payload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Payload] -> ShowS
$cshowList :: [Payload] -> ShowS
show :: Payload -> String
$cshow :: Payload -> String
showsPrec :: Int -> Payload -> ShowS
$cshowsPrec :: Int -> Payload -> ShowS
Show
data Response = SimpleResponse BaseCommand | PayloadResponse BaseCommand MessageMetadata (Maybe Payload) deriving Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
(Int -> Response -> ShowS)
-> (Response -> String) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Response] -> ShowS
$cshowList :: [Response] -> ShowS
show :: Response -> String
$cshow :: Response -> String
showsPrec :: Int -> Response -> ShowS
$cshowsPrec :: Int -> Response -> ShowS
Show
getCommand :: Response -> BaseCommand
getCommand :: Response -> BaseCommand
getCommand response :: Response
response = case Response
response of
(SimpleResponse cmd :: BaseCommand
cmd ) -> BaseCommand
cmd
(PayloadResponse cmd :: BaseCommand
cmd _ _) -> BaseCommand
cmd