{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
module Database.EventStore.Internal.Operation.DeleteStream.Message where
import Data.Int
import Data.ProtocolBuffers
import Database.EventStore.Internal.Operation
import Database.EventStore.Internal.Prelude
data Request
= Request
{ Request -> Required 1 (Value Text)
_streamId :: Required 1 (Value Text)
, Request -> Required 2 (Value Int64)
_expectedVersion :: Required 2 (Value Int64)
, Request -> Required 3 (Value Bool)
_requireMaster :: Required 3 (Value Bool)
, Request -> Optional 4 (Value Bool)
_hardDelete :: Optional 4 (Value Bool)
}
deriving (forall x. Rep Request x -> Request
forall x. Request -> Rep Request x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Request x -> Request
$cfrom :: forall x. Request -> Rep Request x
Generic, Int -> Request -> ShowS
[Request] -> ShowS
Request -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Request] -> ShowS
$cshowList :: [Request] -> ShowS
show :: Request -> String
$cshow :: Request -> String
showsPrec :: Int -> Request -> ShowS
$cshowsPrec :: Int -> Request -> ShowS
Show)
instance Encode Request
newRequest :: Text -> Int64 -> Bool -> Maybe Bool -> Request
newRequest :: Text -> Int64 -> Bool -> Maybe Bool -> Request
newRequest Text
stream_id Int64
exp_ver Bool
req_master Maybe Bool
hard_delete =
Request
{ _streamId :: Required 1 (Value Text)
_streamId = forall a. HasField a => FieldType a -> a
putField Text
stream_id
, _expectedVersion :: Required 2 (Value Int64)
_expectedVersion = forall a. HasField a => FieldType a -> a
putField Int64
exp_ver
, _requireMaster :: Required 3 (Value Bool)
_requireMaster = forall a. HasField a => FieldType a -> a
putField Bool
req_master
, _hardDelete :: Optional 4 (Value Bool)
_hardDelete = forall a. HasField a => FieldType a -> a
putField Maybe Bool
hard_delete
}
data Response
= Response
{ Response -> Required 1 (Enumeration OpResult)
_result :: Required 1 (Enumeration OpResult)
, Response -> Optional 2 (Value Text)
_message :: Optional 2 (Value Text)
, Response -> Optional 3 (Value Int64)
_preparePosition :: Optional 3 (Value Int64)
, Response -> Optional 4 (Value Int64)
_commitPosition :: Optional 4 (Value Int64)
}
deriving (forall x. Rep Response x -> Response
forall x. Response -> Rep Response x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Response x -> Response
$cfrom :: forall x. Response -> Rep Response x
Generic, Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
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)
instance Decode Response