{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds     #-}
--------------------------------------------------------------------------------
-- |
-- Module : Database.EventStore.Internal.Operation.DeleteStream.Message
-- Copyright : (C) 2015 Yorick Laupa
-- License : (see the file LICENSE)
--
-- Maintainer : Yorick Laupa <yo.eight@gmail.com>
-- Stability : provisional
-- Portability : non-portable
--
--------------------------------------------------------------------------------
module Database.EventStore.Internal.Operation.DeleteStream.Message where

--------------------------------------------------------------------------------
import Data.Int

--------------------------------------------------------------------------------
import Data.ProtocolBuffers

--------------------------------------------------------------------------------
import Database.EventStore.Internal.Operation
import Database.EventStore.Internal.Prelude

--------------------------------------------------------------------------------
-- | Delete stream request.
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. Request -> Rep Request x)
-> (forall x. Rep Request x -> Request) -> Generic Request
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
(Int -> Request -> ShowS)
-> (Request -> String) -> ([Request] -> ShowS) -> Show Request
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

--------------------------------------------------------------------------------
-- | 'Request' smart constructor.
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 :: Required 1 (Value Text)
-> Required 2 (Value Int64)
-> Required 3 (Value Bool)
-> Optional 4 (Value Bool)
-> Request
Request
    { _streamId :: Required 1 (Value Text)
_streamId        = FieldType (Field 1 (RequiredField (Always (Value Text))))
-> Field 1 (RequiredField (Always (Value Text)))
forall a. HasField a => FieldType a -> a
putField Text
FieldType (Field 1 (RequiredField (Always (Value Text))))
stream_id
    , _expectedVersion :: Required 2 (Value Int64)
_expectedVersion = FieldType (Field 2 (RequiredField (Always (Value Int64))))
-> Field 2 (RequiredField (Always (Value Int64)))
forall a. HasField a => FieldType a -> a
putField Int64
FieldType (Field 2 (RequiredField (Always (Value Int64))))
exp_ver
    , _requireMaster :: Required 3 (Value Bool)
_requireMaster   = FieldType (Field 3 (RequiredField (Always (Value Bool))))
-> Field 3 (RequiredField (Always (Value Bool)))
forall a. HasField a => FieldType a -> a
putField Bool
FieldType (Field 3 (RequiredField (Always (Value Bool))))
req_master
    , _hardDelete :: Optional 4 (Value Bool)
_hardDelete      = FieldType (Field 4 (OptionalField (Last (Value Bool))))
-> Field 4 (OptionalField (Last (Value Bool)))
forall a. HasField a => FieldType a -> a
putField Maybe Bool
FieldType (Field 4 (OptionalField (Last (Value Bool))))
hard_delete
    }

--------------------------------------------------------------------------------
-- | Delete stream response.
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. Response -> Rep Response x)
-> (forall x. Rep Response x -> Response) -> Generic Response
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
(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)

--------------------------------------------------------------------------------
instance Decode Response