module Network.RPCA.Structs where import Codec.Libevent import Data.Word import qualified Data.IntSet as IS import Data.Binary.Put import Data.Binary.Strict.Get import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BSL import Codec.Libevent.Class data Outboundrequest = Outboundrequest { outboundrequest_id :: Word32, outboundrequest_rpc :: Maybe Rpcrequest, outboundrequest_probe :: Maybe Healthprobe } deriving (Show, Eq) outboundrequestSerialise :: Outboundrequest -> Put outboundrequestSerialise x = do putTaggedWord32 1 (outboundrequest_id x) case (outboundrequest_rpc x) of Nothing -> return () (Just x) -> putTaggedVarBytes 2 $ rpcrequestSerialiseBS (x) case (outboundrequest_probe x) of Nothing -> return () (Just x) -> putTaggedVarBytes 3 $ healthprobeSerialiseBS (x) outboundrequestSerialiseBS = BS.concat . BSL.toChunks . runPut . outboundrequestSerialise outboundrequestEmpty = Outboundrequest 0 Nothing Nothing outboundrequestRequiredElementsSet = IS.fromList [1] outboundrequestDeserialise :: Get Outboundrequest outboundrequestDeserialise = f outboundrequestEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf outboundrequestRequiredElementsSet set) then fail "Outboundrequest did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { outboundrequest_id = v }) (IS.insert 1 set)) 2 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> case (rpcrequestDeserialiseBS v) of { Left err -> fail ("Failed to deserialse Outboundrequest: " ++ err) ; Right result -> f (o {outboundrequest_rpc = (Just result) }) (IS.insert 2 set) }) 3 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> case (healthprobeDeserialiseBS v) of { Left err -> fail ("Failed to deserialse Outboundrequest: " ++ err) ; Right result -> f (o {outboundrequest_probe = (Just result) }) (IS.insert 3 set) }) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set outboundrequestDeserialiseBS = fst . runGet outboundrequestDeserialise instance TaggedStructure Outboundrequest where empty = outboundrequestEmpty serialise = outboundrequestSerialiseBS deserialise = outboundrequestDeserialiseBS data Rpcrequest = Rpcrequest { rpcrequest_service :: String, rpcrequest_method :: String, rpcrequest_checksum :: Maybe Word32 } deriving (Show, Eq) rpcrequestSerialise :: Rpcrequest -> Put rpcrequestSerialise x = do putTaggedString 1 (rpcrequest_service x) putTaggedString 2 (rpcrequest_method x) case (rpcrequest_checksum x) of Nothing -> return () (Just x) -> putTaggedWord32 3 (x) rpcrequestSerialiseBS = BS.concat . BSL.toChunks . runPut . rpcrequestSerialise rpcrequestEmpty = Rpcrequest "" "" Nothing rpcrequestRequiredElementsSet = IS.fromList [1,2] rpcrequestDeserialise :: Get Rpcrequest rpcrequestDeserialise = f rpcrequestEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf rpcrequestRequiredElementsSet set) then fail "Rpcrequest did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> f (o { rpcrequest_service = (decodeString v) }) (IS.insert 1 set)) 2 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> f (o { rpcrequest_method = (decodeString v) }) (IS.insert 2 set)) 3 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { rpcrequest_checksum = (Just v) }) (IS.insert 3 set)) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set rpcrequestDeserialiseBS = fst . runGet rpcrequestDeserialise instance TaggedStructure Rpcrequest where empty = rpcrequestEmpty serialise = rpcrequestSerialiseBS deserialise = rpcrequestDeserialiseBS data Healthprobe = Healthprobe { healthprobe_service :: String } deriving (Show, Eq) healthprobeSerialise :: Healthprobe -> Put healthprobeSerialise x = do putTaggedString 1 (healthprobe_service x) healthprobeSerialiseBS = BS.concat . BSL.toChunks . runPut . healthprobeSerialise healthprobeEmpty = Healthprobe "" healthprobeRequiredElementsSet = IS.fromList [1] healthprobeDeserialise :: Get Healthprobe healthprobeDeserialise = f healthprobeEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf healthprobeRequiredElementsSet set) then fail "Healthprobe did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> f (o { healthprobe_service = (decodeString v) }) (IS.insert 1 set)) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set healthprobeDeserialiseBS = fst . runGet healthprobeDeserialise instance TaggedStructure Healthprobe where empty = healthprobeEmpty serialise = healthprobeSerialiseBS deserialise = healthprobeDeserialiseBS data Inboundreply = Inboundreply { inboundreply_id :: Word32, inboundreply_rpc :: Maybe Rpcreply, inboundreply_health :: Maybe Healthreply } deriving (Show, Eq) inboundreplySerialise :: Inboundreply -> Put inboundreplySerialise x = do putTaggedWord32 1 (inboundreply_id x) case (inboundreply_rpc x) of Nothing -> return () (Just x) -> putTaggedVarBytes 2 $ rpcreplySerialiseBS (x) case (inboundreply_health x) of Nothing -> return () (Just x) -> putTaggedVarBytes 3 $ healthreplySerialiseBS (x) inboundreplySerialiseBS = BS.concat . BSL.toChunks . runPut . inboundreplySerialise inboundreplyEmpty = Inboundreply 0 Nothing Nothing inboundreplyRequiredElementsSet = IS.fromList [1] inboundreplyDeserialise :: Get Inboundreply inboundreplyDeserialise = f inboundreplyEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf inboundreplyRequiredElementsSet set) then fail "Inboundreply did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { inboundreply_id = v }) (IS.insert 1 set)) 2 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> case (rpcreplyDeserialiseBS v) of { Left err -> fail ("Failed to deserialse Inboundreply: " ++ err) ; Right result -> f (o {inboundreply_rpc = (Just result) }) (IS.insert 2 set) }) 3 -> getLengthPrefixed >>= getByteString . fromIntegral >>= (\v -> case (healthreplyDeserialiseBS v) of { Left err -> fail ("Failed to deserialse Inboundreply: " ++ err) ; Right result -> f (o {inboundreply_health = (Just result) }) (IS.insert 3 set) }) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set inboundreplyDeserialiseBS = fst . runGet inboundreplyDeserialise instance TaggedStructure Inboundreply where empty = inboundreplyEmpty serialise = inboundreplySerialiseBS deserialise = inboundreplyDeserialiseBS data Rpcreply = Rpcreply { rpcreply_reply_code :: Word32, rpcreply_checksum :: Maybe Word32 } deriving (Show, Eq) rpcreplySerialise :: Rpcreply -> Put rpcreplySerialise x = do putTaggedWord32 1 (rpcreply_reply_code x) case (rpcreply_checksum x) of Nothing -> return () (Just x) -> putTaggedWord32 2 (x) rpcreplySerialiseBS = BS.concat . BSL.toChunks . runPut . rpcreplySerialise rpcreplyEmpty = Rpcreply 0 Nothing rpcreplyRequiredElementsSet = IS.fromList [1] rpcreplyDeserialise :: Get Rpcreply rpcreplyDeserialise = f rpcreplyEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf rpcreplyRequiredElementsSet set) then fail "Rpcreply did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { rpcreply_reply_code = v }) (IS.insert 1 set)) 2 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { rpcreply_checksum = (Just v) }) (IS.insert 2 set)) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set rpcreplyDeserialiseBS = fst . runGet rpcreplyDeserialise instance TaggedStructure Rpcreply where empty = rpcreplyEmpty serialise = rpcreplySerialiseBS deserialise = rpcreplyDeserialiseBS data Healthreply = Healthreply { healthreply_good :: Word32 } deriving (Show, Eq) healthreplySerialise :: Healthreply -> Put healthreplySerialise x = do putTaggedWord32 1 (healthreply_good x) healthreplySerialiseBS = BS.concat . BSL.toChunks . runPut . healthreplySerialise healthreplyEmpty = Healthreply 0 healthreplyRequiredElementsSet = IS.fromList [1] healthreplyDeserialise :: Get Healthreply healthreplyDeserialise = f healthreplyEmpty IS.empty where f o set = do emptyp <- isEmpty if emptyp then if not (IS.isSubsetOf healthreplyRequiredElementsSet set) then fail "Healthreply did not contain all required elements" else return o else do tag <- getBase128 case tag of 1 -> getWord8 >> getLengthPrefixed >>= (\v -> f (o { healthreply_good = v }) (IS.insert 1 set)) otherwise -> getLengthPrefixed >>= getByteString . fromIntegral >> f o set healthreplyDeserialiseBS = fst . runGet healthreplyDeserialise instance TaggedStructure Healthreply where empty = healthreplyEmpty serialise = healthreplySerialiseBS deserialise = healthreplyDeserialiseBS