{-# LANGUAGE ScopedTypeVariables, DataKinds, TypeFamilies, UndecidableInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternSynonyms, MagicHash, NoImplicitPrelude, DataKinds, BangPatterns, TypeApplications, OverloadedStrings, DerivingStrategies#-}
{-# OPTIONS_GHC -Wno-unused-imports#-}
{-# OPTIONS_GHC -Wno-duplicate-exports#-}
{-# OPTIONS_GHC -Wno-dodgy-exports#-}
module Proto.PulsarApi (
AuthData(), AuthMethod(..), AuthMethod(), BaseCommand(),
BaseCommand'Type(..), BaseCommand'Type(), CommandAck(),
CommandAck'AckType(..), CommandAck'AckType(),
CommandAck'ValidationError(..), CommandAck'ValidationError(),
CommandAckResponse(), CommandActiveConsumerChange(),
CommandAddPartitionToTxn(), CommandAddPartitionToTxnResponse(),
CommandAddSubscriptionToTxn(),
CommandAddSubscriptionToTxnResponse(), CommandAuthChallenge(),
CommandAuthResponse(), CommandCloseConsumer(),
CommandCloseProducer(), CommandConnect(), CommandConnected(),
CommandConsumerStats(), CommandConsumerStatsResponse(),
CommandEndTxn(), CommandEndTxnOnPartition(),
CommandEndTxnOnPartitionResponse(), CommandEndTxnOnSubscription(),
CommandEndTxnOnSubscriptionResponse(), CommandEndTxnResponse(),
CommandError(), CommandFlow(), CommandGetLastMessageId(),
CommandGetLastMessageIdResponse(), CommandGetOrCreateSchema(),
CommandGetOrCreateSchemaResponse(), CommandGetSchema(),
CommandGetSchemaResponse(), CommandGetTopicsOfNamespace(),
CommandGetTopicsOfNamespace'Mode(..),
CommandGetTopicsOfNamespace'Mode(),
CommandGetTopicsOfNamespaceResponse(), CommandLookupTopic(),
CommandLookupTopicResponse(),
CommandLookupTopicResponse'LookupType(..),
CommandLookupTopicResponse'LookupType(), CommandMessage(),
CommandNewTxn(), CommandNewTxnResponse(),
CommandPartitionedTopicMetadata(),
CommandPartitionedTopicMetadataResponse(),
CommandPartitionedTopicMetadataResponse'LookupType(..),
CommandPartitionedTopicMetadataResponse'LookupType(),
CommandPing(), CommandPong(), CommandProducer(),
CommandProducerSuccess(), CommandReachedEndOfTopic(),
CommandRedeliverUnacknowledgedMessages(), CommandSeek(),
CommandSend(), CommandSendError(), CommandSendReceipt(),
CommandSubscribe(), CommandSubscribe'InitialPosition(..),
CommandSubscribe'InitialPosition(), CommandSubscribe'SubType(..),
CommandSubscribe'SubType(), CommandSuccess(), CommandUnsubscribe(),
CompressionType(..), CompressionType(), EncryptionKeys(),
FeatureFlags(), IntRange(), KeyLongValue(), KeySharedMeta(),
KeySharedMode(..), KeySharedMode(), KeyValue(), MessageIdData(),
MessageMetadata(), ProtocolVersion(..), ProtocolVersion(),
Schema(), Schema'Type(..), Schema'Type(), ServerError(..),
ServerError(), SingleMessageMetadata(), Subscription(),
TxnAction(..), TxnAction()
) where
import qualified Data.ProtoLens.Runtime.Control.DeepSeq as Control.DeepSeq
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Prism as Data.ProtoLens.Prism
import qualified Data.ProtoLens.Runtime.Prelude as Prelude
import qualified Data.ProtoLens.Runtime.Data.Int as Data.Int
import qualified Data.ProtoLens.Runtime.Data.Monoid as Data.Monoid
import qualified Data.ProtoLens.Runtime.Data.Word as Data.Word
import qualified Data.ProtoLens.Runtime.Data.ProtoLens as Data.ProtoLens
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Bytes as Data.ProtoLens.Encoding.Bytes
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Growing as Data.ProtoLens.Encoding.Growing
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Parser.Unsafe as Data.ProtoLens.Encoding.Parser.Unsafe
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Wire as Data.ProtoLens.Encoding.Wire
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Field as Data.ProtoLens.Field
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Message.Enum as Data.ProtoLens.Message.Enum
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Service.Types as Data.ProtoLens.Service.Types
import qualified Data.ProtoLens.Runtime.Lens.Family2 as Lens.Family2
import qualified Data.ProtoLens.Runtime.Lens.Family2.Unchecked as Lens.Family2.Unchecked
import qualified Data.ProtoLens.Runtime.Data.Text as Data.Text
import qualified Data.ProtoLens.Runtime.Data.Map as Data.Map
import qualified Data.ProtoLens.Runtime.Data.ByteString as Data.ByteString
import qualified Data.ProtoLens.Runtime.Data.ByteString.Char8 as Data.ByteString.Char8
import qualified Data.ProtoLens.Runtime.Data.Text.Encoding as Data.Text.Encoding
import qualified Data.ProtoLens.Runtime.Data.Vector as Data.Vector
import qualified Data.ProtoLens.Runtime.Data.Vector.Generic as Data.Vector.Generic
import qualified Data.ProtoLens.Runtime.Data.Vector.Unboxed as Data.Vector.Unboxed
import qualified Data.ProtoLens.Runtime.Text.Read as Text.Read
data AuthData
= AuthData'_constructor {AuthData -> Maybe Text
_AuthData'authMethodName :: !(Prelude.Maybe Data.Text.Text),
AuthData -> Maybe ByteString
_AuthData'authData :: !(Prelude.Maybe Data.ByteString.ByteString),
AuthData -> FieldSet
_AuthData'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (AuthData -> AuthData -> Bool
(AuthData -> AuthData -> Bool)
-> (AuthData -> AuthData -> Bool) -> Eq AuthData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthData -> AuthData -> Bool
$c/= :: AuthData -> AuthData -> Bool
== :: AuthData -> AuthData -> Bool
$c== :: AuthData -> AuthData -> Bool
Prelude.Eq, Eq AuthData
Eq AuthData =>
(AuthData -> AuthData -> Ordering)
-> (AuthData -> AuthData -> Bool)
-> (AuthData -> AuthData -> Bool)
-> (AuthData -> AuthData -> Bool)
-> (AuthData -> AuthData -> Bool)
-> (AuthData -> AuthData -> AuthData)
-> (AuthData -> AuthData -> AuthData)
-> Ord AuthData
AuthData -> AuthData -> Bool
AuthData -> AuthData -> Ordering
AuthData -> AuthData -> AuthData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AuthData -> AuthData -> AuthData
$cmin :: AuthData -> AuthData -> AuthData
max :: AuthData -> AuthData -> AuthData
$cmax :: AuthData -> AuthData -> AuthData
>= :: AuthData -> AuthData -> Bool
$c>= :: AuthData -> AuthData -> Bool
> :: AuthData -> AuthData -> Bool
$c> :: AuthData -> AuthData -> Bool
<= :: AuthData -> AuthData -> Bool
$c<= :: AuthData -> AuthData -> Bool
< :: AuthData -> AuthData -> Bool
$c< :: AuthData -> AuthData -> Bool
compare :: AuthData -> AuthData -> Ordering
$ccompare :: AuthData -> AuthData -> Ordering
$cp1Ord :: Eq AuthData
Prelude.Ord)
instance Prelude.Show AuthData where
showsPrec :: Int -> AuthData -> ShowS
showsPrec _ __x :: AuthData
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(AuthData -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort AuthData
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField AuthData "authMethodName" Data.Text.Text where
fieldOf :: Proxy# "authMethodName"
-> (Text -> f Text) -> AuthData -> f AuthData
fieldOf _
= ((Maybe Text -> f (Maybe Text)) -> AuthData -> f AuthData)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> AuthData
-> f AuthData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AuthData -> Maybe Text)
-> (AuthData -> Maybe Text -> AuthData)
-> Lens AuthData AuthData (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AuthData -> Maybe Text
_AuthData'authMethodName
(\ x__ :: AuthData
x__ y__ :: Maybe Text
y__ -> AuthData
x__ {_AuthData'authMethodName :: Maybe Text
_AuthData'authMethodName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField AuthData "maybe'authMethodName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'authMethodName"
-> (Maybe Text -> f (Maybe Text)) -> AuthData -> f AuthData
fieldOf _
= ((Maybe Text -> f (Maybe Text)) -> AuthData -> f AuthData)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> AuthData
-> f AuthData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AuthData -> Maybe Text)
-> (AuthData -> Maybe Text -> AuthData)
-> Lens AuthData AuthData (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AuthData -> Maybe Text
_AuthData'authMethodName
(\ x__ :: AuthData
x__ y__ :: Maybe Text
y__ -> AuthData
x__ {_AuthData'authMethodName :: Maybe Text
_AuthData'authMethodName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField AuthData "authData" Data.ByteString.ByteString where
fieldOf :: Proxy# "authData"
-> (ByteString -> f ByteString) -> AuthData -> f AuthData
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> AuthData -> f AuthData)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> AuthData
-> f AuthData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AuthData -> Maybe ByteString)
-> (AuthData -> Maybe ByteString -> AuthData)
-> Lens AuthData AuthData (Maybe ByteString) (Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AuthData -> Maybe ByteString
_AuthData'authData (\ x__ :: AuthData
x__ y__ :: Maybe ByteString
y__ -> AuthData
x__ {_AuthData'authData :: Maybe ByteString
_AuthData'authData = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField AuthData "maybe'authData" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'authData"
-> (Maybe ByteString -> f (Maybe ByteString))
-> AuthData
-> f AuthData
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> AuthData -> f AuthData)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> AuthData
-> f AuthData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AuthData -> Maybe ByteString)
-> (AuthData -> Maybe ByteString -> AuthData)
-> Lens AuthData AuthData (Maybe ByteString) (Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AuthData -> Maybe ByteString
_AuthData'authData (\ x__ :: AuthData
x__ y__ :: Maybe ByteString
y__ -> AuthData
x__ {_AuthData'authData :: Maybe ByteString
_AuthData'authData = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message AuthData where
messageName :: Proxy AuthData -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.AuthData"
packedMessageDescriptor :: Proxy AuthData -> ByteString
packedMessageDescriptor _
= "\n\
\\bAuthData\DC2(\n\
\\DLEauth_method_name\CAN\SOH \SOH(\tR\SOauthMethodName\DC2\ESC\n\
\\tauth_data\CAN\STX \SOH(\fR\bauthData"
packedFileDescriptor :: Proxy AuthData -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor AuthData)
fieldsByTag
= let
authMethodName__field_descriptor :: FieldDescriptor AuthData
authMethodName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor AuthData Text
-> FieldDescriptor AuthData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"auth_method_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens AuthData AuthData (Maybe Text) (Maybe Text)
-> FieldAccessor AuthData Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethodName")) ::
Data.ProtoLens.FieldDescriptor AuthData
authData__field_descriptor :: FieldDescriptor AuthData
authData__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor AuthData ByteString
-> FieldDescriptor AuthData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"auth_data"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens AuthData AuthData (Maybe ByteString) (Maybe ByteString)
-> FieldAccessor AuthData ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authData")) ::
Data.ProtoLens.FieldDescriptor AuthData
in
[(Tag, FieldDescriptor AuthData)]
-> Map Tag (FieldDescriptor AuthData)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor AuthData
authMethodName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor AuthData
authData__field_descriptor)]
unknownFields :: LensLike' f AuthData FieldSet
unknownFields
= (AuthData -> FieldSet)
-> (AuthData -> FieldSet -> AuthData) -> Lens' AuthData FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AuthData -> FieldSet
_AuthData'_unknownFields
(\ x__ :: AuthData
x__ y__ :: FieldSet
y__ -> AuthData
x__ {_AuthData'_unknownFields :: FieldSet
_AuthData'_unknownFields = FieldSet
y__})
defMessage :: AuthData
defMessage
= $WAuthData'_constructor :: Maybe Text -> Maybe ByteString -> FieldSet -> AuthData
AuthData'_constructor
{_AuthData'authMethodName :: Maybe Text
_AuthData'authMethodName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_AuthData'authData :: Maybe ByteString
_AuthData'authData = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_AuthData'_unknownFields :: FieldSet
_AuthData'_unknownFields = []}
parseMessage :: Parser AuthData
parseMessage
= let
loop :: AuthData -> Data.ProtoLens.Encoding.Bytes.Parser AuthData
loop :: AuthData -> Parser AuthData
loop x :: AuthData
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
AuthData -> Parser AuthData
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter AuthData AuthData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> AuthData -> AuthData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter AuthData AuthData FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) AuthData
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"auth_method_name"
AuthData -> Parser AuthData
loop
(Setter AuthData AuthData Text Text -> Text -> AuthData -> AuthData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authMethodName") Text
y AuthData
x)
18
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"auth_data"
AuthData -> Parser AuthData
loop
(Setter AuthData AuthData ByteString ByteString
-> ByteString -> AuthData -> AuthData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authData") ByteString
y AuthData
x)
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
AuthData -> Parser AuthData
loop
(Setter AuthData AuthData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> AuthData -> AuthData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter AuthData AuthData FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) AuthData
x)
in
Parser AuthData -> String -> Parser AuthData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do AuthData -> Parser AuthData
loop AuthData
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "AuthData"
buildMessage :: AuthData -> Builder
buildMessage
= \ _x :: AuthData
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike (Maybe Text) AuthData AuthData (Maybe Text) (Maybe Text)
-> AuthData -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethodName") AuthData
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
AuthData
AuthData
(Maybe ByteString)
(Maybe ByteString)
-> AuthData -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authData") AuthData
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet AuthData AuthData FieldSet FieldSet
-> AuthData -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet AuthData AuthData FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields AuthData
_x)))
instance Control.DeepSeq.NFData AuthData where
rnf :: AuthData -> ()
rnf
= \ x__ :: AuthData
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(AuthData -> FieldSet
_AuthData'_unknownFields AuthData
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(AuthData -> Maybe Text
_AuthData'authMethodName AuthData
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (AuthData -> Maybe ByteString
_AuthData'authData AuthData
x__) ()))
data AuthMethod
= AuthMethodNone | AuthMethodYcaV1 | AuthMethodAthens
deriving stock (Int -> AuthMethod -> ShowS
[AuthMethod] -> ShowS
AuthMethod -> String
(Int -> AuthMethod -> ShowS)
-> (AuthMethod -> String)
-> ([AuthMethod] -> ShowS)
-> Show AuthMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthMethod] -> ShowS
$cshowList :: [AuthMethod] -> ShowS
show :: AuthMethod -> String
$cshow :: AuthMethod -> String
showsPrec :: Int -> AuthMethod -> ShowS
$cshowsPrec :: Int -> AuthMethod -> ShowS
Prelude.Show, AuthMethod -> AuthMethod -> Bool
(AuthMethod -> AuthMethod -> Bool)
-> (AuthMethod -> AuthMethod -> Bool) -> Eq AuthMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthMethod -> AuthMethod -> Bool
$c/= :: AuthMethod -> AuthMethod -> Bool
== :: AuthMethod -> AuthMethod -> Bool
$c== :: AuthMethod -> AuthMethod -> Bool
Prelude.Eq, Eq AuthMethod
Eq AuthMethod =>
(AuthMethod -> AuthMethod -> Ordering)
-> (AuthMethod -> AuthMethod -> Bool)
-> (AuthMethod -> AuthMethod -> Bool)
-> (AuthMethod -> AuthMethod -> Bool)
-> (AuthMethod -> AuthMethod -> Bool)
-> (AuthMethod -> AuthMethod -> AuthMethod)
-> (AuthMethod -> AuthMethod -> AuthMethod)
-> Ord AuthMethod
AuthMethod -> AuthMethod -> Bool
AuthMethod -> AuthMethod -> Ordering
AuthMethod -> AuthMethod -> AuthMethod
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AuthMethod -> AuthMethod -> AuthMethod
$cmin :: AuthMethod -> AuthMethod -> AuthMethod
max :: AuthMethod -> AuthMethod -> AuthMethod
$cmax :: AuthMethod -> AuthMethod -> AuthMethod
>= :: AuthMethod -> AuthMethod -> Bool
$c>= :: AuthMethod -> AuthMethod -> Bool
> :: AuthMethod -> AuthMethod -> Bool
$c> :: AuthMethod -> AuthMethod -> Bool
<= :: AuthMethod -> AuthMethod -> Bool
$c<= :: AuthMethod -> AuthMethod -> Bool
< :: AuthMethod -> AuthMethod -> Bool
$c< :: AuthMethod -> AuthMethod -> Bool
compare :: AuthMethod -> AuthMethod -> Ordering
$ccompare :: AuthMethod -> AuthMethod -> Ordering
$cp1Ord :: Eq AuthMethod
Prelude.Ord)
instance Data.ProtoLens.MessageEnum AuthMethod where
maybeToEnum :: Int -> Maybe AuthMethod
maybeToEnum 0 = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodNone
maybeToEnum 1 = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodYcaV1
maybeToEnum 2 = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodAthens
maybeToEnum _ = Maybe AuthMethod
forall a. Maybe a
Prelude.Nothing
showEnum :: AuthMethod -> String
showEnum AuthMethodNone = "AuthMethodNone"
showEnum AuthMethodYcaV1 = "AuthMethodYcaV1"
showEnum AuthMethodAthens = "AuthMethodAthens"
readEnum :: String -> Maybe AuthMethod
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AuthMethodNone" = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodNone
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AuthMethodYcaV1" = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodYcaV1
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AuthMethodAthens" = AuthMethod -> Maybe AuthMethod
forall a. a -> Maybe a
Prelude.Just AuthMethod
AuthMethodAthens
| Bool
Prelude.otherwise
= Maybe Int -> (Int -> Maybe AuthMethod) -> Maybe AuthMethod
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe AuthMethod
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded AuthMethod where
minBound :: AuthMethod
minBound = AuthMethod
AuthMethodNone
maxBound :: AuthMethod
maxBound = AuthMethod
AuthMethodAthens
instance Prelude.Enum AuthMethod where
toEnum :: Int -> AuthMethod
toEnum k__ :: Int
k__
= AuthMethod
-> (AuthMethod -> AuthMethod) -> Maybe AuthMethod -> AuthMethod
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> AuthMethod
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum AuthMethod: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
AuthMethod -> AuthMethod
forall a. a -> a
Prelude.id
(Int -> Maybe AuthMethod
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: AuthMethod -> Int
fromEnum AuthMethodNone = 0
fromEnum AuthMethodYcaV1 = 1
fromEnum AuthMethodAthens = 2
succ :: AuthMethod -> AuthMethod
succ AuthMethodAthens
= String -> AuthMethod
forall a. HasCallStack => String -> a
Prelude.error
"AuthMethod.succ: bad argument AuthMethodAthens. This value would be out of bounds."
succ AuthMethodNone = AuthMethod
AuthMethodYcaV1
succ AuthMethodYcaV1 = AuthMethod
AuthMethodAthens
pred :: AuthMethod -> AuthMethod
pred AuthMethodNone
= String -> AuthMethod
forall a. HasCallStack => String -> a
Prelude.error
"AuthMethod.pred: bad argument AuthMethodNone. This value would be out of bounds."
pred AuthMethodYcaV1 = AuthMethod
AuthMethodNone
pred AuthMethodAthens = AuthMethod
AuthMethodYcaV1
enumFrom :: AuthMethod -> [AuthMethod]
enumFrom = AuthMethod -> [AuthMethod]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: AuthMethod -> AuthMethod -> [AuthMethod]
enumFromTo = AuthMethod -> AuthMethod -> [AuthMethod]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: AuthMethod -> AuthMethod -> [AuthMethod]
enumFromThen = AuthMethod -> AuthMethod -> [AuthMethod]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: AuthMethod -> AuthMethod -> AuthMethod -> [AuthMethod]
enumFromThenTo = AuthMethod -> AuthMethod -> AuthMethod -> [AuthMethod]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault AuthMethod where
fieldDefault :: AuthMethod
fieldDefault = AuthMethod
AuthMethodNone
instance Control.DeepSeq.NFData AuthMethod where
rnf :: AuthMethod -> ()
rnf x__ :: AuthMethod
x__ = AuthMethod -> () -> ()
forall a b. a -> b -> b
Prelude.seq AuthMethod
x__ ()
data BaseCommand
= BaseCommand'_constructor {BaseCommand -> BaseCommand'Type
_BaseCommand'type' :: !BaseCommand'Type,
BaseCommand -> Maybe CommandConnect
_BaseCommand'connect :: !(Prelude.Maybe CommandConnect),
BaseCommand -> Maybe CommandConnected
_BaseCommand'connected :: !(Prelude.Maybe CommandConnected),
BaseCommand -> Maybe CommandSubscribe
_BaseCommand'subscribe :: !(Prelude.Maybe CommandSubscribe),
BaseCommand -> Maybe CommandProducer
_BaseCommand'producer :: !(Prelude.Maybe CommandProducer),
BaseCommand -> Maybe CommandSend
_BaseCommand'send :: !(Prelude.Maybe CommandSend),
BaseCommand -> Maybe CommandSendReceipt
_BaseCommand'sendReceipt :: !(Prelude.Maybe CommandSendReceipt),
BaseCommand -> Maybe CommandSendError
_BaseCommand'sendError :: !(Prelude.Maybe CommandSendError),
BaseCommand -> Maybe CommandMessage
_BaseCommand'message :: !(Prelude.Maybe CommandMessage),
BaseCommand -> Maybe CommandAck
_BaseCommand'ack :: !(Prelude.Maybe CommandAck),
BaseCommand -> Maybe CommandFlow
_BaseCommand'flow :: !(Prelude.Maybe CommandFlow),
BaseCommand -> Maybe CommandUnsubscribe
_BaseCommand'unsubscribe :: !(Prelude.Maybe CommandUnsubscribe),
BaseCommand -> Maybe CommandSuccess
_BaseCommand'success :: !(Prelude.Maybe CommandSuccess),
BaseCommand -> Maybe CommandError
_BaseCommand'error :: !(Prelude.Maybe CommandError),
BaseCommand -> Maybe CommandCloseProducer
_BaseCommand'closeProducer :: !(Prelude.Maybe CommandCloseProducer),
BaseCommand -> Maybe CommandCloseConsumer
_BaseCommand'closeConsumer :: !(Prelude.Maybe CommandCloseConsumer),
BaseCommand -> Maybe CommandProducerSuccess
_BaseCommand'producerSuccess :: !(Prelude.Maybe CommandProducerSuccess),
BaseCommand -> Maybe CommandPing
_BaseCommand'ping :: !(Prelude.Maybe CommandPing),
BaseCommand -> Maybe CommandPong
_BaseCommand'pong :: !(Prelude.Maybe CommandPong),
BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages :: !(Prelude.Maybe CommandRedeliverUnacknowledgedMessages),
BaseCommand -> Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata :: !(Prelude.Maybe CommandPartitionedTopicMetadata),
BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse :: !(Prelude.Maybe CommandPartitionedTopicMetadataResponse),
BaseCommand -> Maybe CommandLookupTopic
_BaseCommand'lookupTopic :: !(Prelude.Maybe CommandLookupTopic),
BaseCommand -> Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse :: !(Prelude.Maybe CommandLookupTopicResponse),
BaseCommand -> Maybe CommandConsumerStats
_BaseCommand'consumerStats :: !(Prelude.Maybe CommandConsumerStats),
BaseCommand -> Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse :: !(Prelude.Maybe CommandConsumerStatsResponse),
BaseCommand -> Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic :: !(Prelude.Maybe CommandReachedEndOfTopic),
BaseCommand -> Maybe CommandSeek
_BaseCommand'seek :: !(Prelude.Maybe CommandSeek),
BaseCommand -> Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId :: !(Prelude.Maybe CommandGetLastMessageId),
BaseCommand -> Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse :: !(Prelude.Maybe CommandGetLastMessageIdResponse),
BaseCommand -> Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange :: !(Prelude.Maybe CommandActiveConsumerChange),
BaseCommand -> Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace :: !(Prelude.Maybe CommandGetTopicsOfNamespace),
BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse :: !(Prelude.Maybe CommandGetTopicsOfNamespaceResponse),
BaseCommand -> Maybe CommandGetSchema
_BaseCommand'getSchema :: !(Prelude.Maybe CommandGetSchema),
BaseCommand -> Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse :: !(Prelude.Maybe CommandGetSchemaResponse),
BaseCommand -> Maybe CommandAuthChallenge
_BaseCommand'authChallenge :: !(Prelude.Maybe CommandAuthChallenge),
BaseCommand -> Maybe CommandAuthResponse
_BaseCommand'authResponse :: !(Prelude.Maybe CommandAuthResponse),
BaseCommand -> Maybe CommandAckResponse
_BaseCommand'ackResponse :: !(Prelude.Maybe CommandAckResponse),
BaseCommand -> Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema :: !(Prelude.Maybe CommandGetOrCreateSchema),
BaseCommand -> Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse :: !(Prelude.Maybe CommandGetOrCreateSchemaResponse),
BaseCommand -> Maybe CommandNewTxn
_BaseCommand'newTxn :: !(Prelude.Maybe CommandNewTxn),
BaseCommand -> Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse :: !(Prelude.Maybe CommandNewTxnResponse),
BaseCommand -> Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn :: !(Prelude.Maybe CommandAddPartitionToTxn),
BaseCommand -> Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse :: !(Prelude.Maybe CommandAddPartitionToTxnResponse),
BaseCommand -> Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn :: !(Prelude.Maybe CommandAddSubscriptionToTxn),
BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse :: !(Prelude.Maybe CommandAddSubscriptionToTxnResponse),
BaseCommand -> Maybe CommandEndTxn
_BaseCommand'endTxn :: !(Prelude.Maybe CommandEndTxn),
BaseCommand -> Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse :: !(Prelude.Maybe CommandEndTxnResponse),
BaseCommand -> Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition :: !(Prelude.Maybe CommandEndTxnOnPartition),
BaseCommand -> Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse :: !(Prelude.Maybe CommandEndTxnOnPartitionResponse),
BaseCommand -> Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription :: !(Prelude.Maybe CommandEndTxnOnSubscription),
BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse :: !(Prelude.Maybe CommandEndTxnOnSubscriptionResponse),
BaseCommand -> FieldSet
_BaseCommand'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (BaseCommand -> BaseCommand -> Bool
(BaseCommand -> BaseCommand -> Bool)
-> (BaseCommand -> BaseCommand -> Bool) -> Eq BaseCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BaseCommand -> BaseCommand -> Bool
$c/= :: BaseCommand -> BaseCommand -> Bool
== :: BaseCommand -> BaseCommand -> Bool
$c== :: BaseCommand -> BaseCommand -> Bool
Prelude.Eq, Eq BaseCommand
Eq BaseCommand =>
(BaseCommand -> BaseCommand -> Ordering)
-> (BaseCommand -> BaseCommand -> Bool)
-> (BaseCommand -> BaseCommand -> Bool)
-> (BaseCommand -> BaseCommand -> Bool)
-> (BaseCommand -> BaseCommand -> Bool)
-> (BaseCommand -> BaseCommand -> BaseCommand)
-> (BaseCommand -> BaseCommand -> BaseCommand)
-> Ord BaseCommand
BaseCommand -> BaseCommand -> Bool
BaseCommand -> BaseCommand -> Ordering
BaseCommand -> BaseCommand -> BaseCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BaseCommand -> BaseCommand -> BaseCommand
$cmin :: BaseCommand -> BaseCommand -> BaseCommand
max :: BaseCommand -> BaseCommand -> BaseCommand
$cmax :: BaseCommand -> BaseCommand -> BaseCommand
>= :: BaseCommand -> BaseCommand -> Bool
$c>= :: BaseCommand -> BaseCommand -> Bool
> :: BaseCommand -> BaseCommand -> Bool
$c> :: BaseCommand -> BaseCommand -> Bool
<= :: BaseCommand -> BaseCommand -> Bool
$c<= :: BaseCommand -> BaseCommand -> Bool
< :: BaseCommand -> BaseCommand -> Bool
$c< :: BaseCommand -> BaseCommand -> Bool
compare :: BaseCommand -> BaseCommand -> Ordering
$ccompare :: BaseCommand -> BaseCommand -> Ordering
$cp1Ord :: Eq BaseCommand
Prelude.Ord)
instance Prelude.Show BaseCommand where
showsPrec :: Int -> BaseCommand -> ShowS
showsPrec _ __x :: BaseCommand
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(BaseCommand -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort BaseCommand
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField BaseCommand "type'" BaseCommand'Type where
fieldOf :: Proxy# "type'"
-> (BaseCommand'Type -> f BaseCommand'Type)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((BaseCommand'Type -> f BaseCommand'Type)
-> BaseCommand -> f BaseCommand)
-> ((BaseCommand'Type -> f BaseCommand'Type)
-> BaseCommand'Type -> f BaseCommand'Type)
-> (BaseCommand'Type -> f BaseCommand'Type)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> BaseCommand'Type)
-> (BaseCommand -> BaseCommand'Type -> BaseCommand)
-> Lens BaseCommand BaseCommand BaseCommand'Type BaseCommand'Type
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> BaseCommand'Type
_BaseCommand'type' (\ x__ :: BaseCommand
x__ y__ :: BaseCommand'Type
y__ -> BaseCommand
x__ {_BaseCommand'type' :: BaseCommand'Type
_BaseCommand'type' = BaseCommand'Type
y__}))
(BaseCommand'Type -> f BaseCommand'Type)
-> BaseCommand'Type -> f BaseCommand'Type
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "connect" CommandConnect where
fieldOf :: Proxy# "connect"
-> (CommandConnect -> f CommandConnect)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConnect -> f (Maybe CommandConnect))
-> BaseCommand -> f BaseCommand)
-> ((CommandConnect -> f CommandConnect)
-> Maybe CommandConnect -> f (Maybe CommandConnect))
-> (CommandConnect -> f CommandConnect)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConnect)
-> (BaseCommand -> Maybe CommandConnect -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConnect)
(Maybe CommandConnect)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConnect
_BaseCommand'connect
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConnect
y__ -> BaseCommand
x__ {_BaseCommand'connect :: Maybe CommandConnect
_BaseCommand'connect = Maybe CommandConnect
y__}))
(CommandConnect -> Lens' (Maybe CommandConnect) CommandConnect
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandConnect
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'connect" (Prelude.Maybe CommandConnect) where
fieldOf :: Proxy# "maybe'connect"
-> (Maybe CommandConnect -> f (Maybe CommandConnect))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConnect -> f (Maybe CommandConnect))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandConnect -> f (Maybe CommandConnect))
-> Maybe CommandConnect -> f (Maybe CommandConnect))
-> (Maybe CommandConnect -> f (Maybe CommandConnect))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConnect)
-> (BaseCommand -> Maybe CommandConnect -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConnect)
(Maybe CommandConnect)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConnect
_BaseCommand'connect
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConnect
y__ -> BaseCommand
x__ {_BaseCommand'connect :: Maybe CommandConnect
_BaseCommand'connect = Maybe CommandConnect
y__}))
(Maybe CommandConnect -> f (Maybe CommandConnect))
-> Maybe CommandConnect -> f (Maybe CommandConnect)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "connected" CommandConnected where
fieldOf :: Proxy# "connected"
-> (CommandConnected -> f CommandConnected)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConnected -> f (Maybe CommandConnected))
-> BaseCommand -> f BaseCommand)
-> ((CommandConnected -> f CommandConnected)
-> Maybe CommandConnected -> f (Maybe CommandConnected))
-> (CommandConnected -> f CommandConnected)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConnected)
-> (BaseCommand -> Maybe CommandConnected -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConnected)
(Maybe CommandConnected)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConnected
_BaseCommand'connected
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConnected
y__ -> BaseCommand
x__ {_BaseCommand'connected :: Maybe CommandConnected
_BaseCommand'connected = Maybe CommandConnected
y__}))
(CommandConnected -> Lens' (Maybe CommandConnected) CommandConnected
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandConnected
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'connected" (Prelude.Maybe CommandConnected) where
fieldOf :: Proxy# "maybe'connected"
-> (Maybe CommandConnected -> f (Maybe CommandConnected))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConnected -> f (Maybe CommandConnected))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandConnected -> f (Maybe CommandConnected))
-> Maybe CommandConnected -> f (Maybe CommandConnected))
-> (Maybe CommandConnected -> f (Maybe CommandConnected))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConnected)
-> (BaseCommand -> Maybe CommandConnected -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConnected)
(Maybe CommandConnected)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConnected
_BaseCommand'connected
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConnected
y__ -> BaseCommand
x__ {_BaseCommand'connected :: Maybe CommandConnected
_BaseCommand'connected = Maybe CommandConnected
y__}))
(Maybe CommandConnected -> f (Maybe CommandConnected))
-> Maybe CommandConnected -> f (Maybe CommandConnected)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "subscribe" CommandSubscribe where
fieldOf :: Proxy# "subscribe"
-> (CommandSubscribe -> f CommandSubscribe)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> BaseCommand -> f BaseCommand)
-> ((CommandSubscribe -> f CommandSubscribe)
-> Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> (CommandSubscribe -> f CommandSubscribe)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSubscribe)
-> (BaseCommand -> Maybe CommandSubscribe -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSubscribe)
(Maybe CommandSubscribe)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSubscribe
_BaseCommand'subscribe
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSubscribe
y__ -> BaseCommand
x__ {_BaseCommand'subscribe :: Maybe CommandSubscribe
_BaseCommand'subscribe = Maybe CommandSubscribe
y__}))
(CommandSubscribe -> Lens' (Maybe CommandSubscribe) CommandSubscribe
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSubscribe
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'subscribe" (Prelude.Maybe CommandSubscribe) where
fieldOf :: Proxy# "maybe'subscribe"
-> (Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> (Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSubscribe)
-> (BaseCommand -> Maybe CommandSubscribe -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSubscribe)
(Maybe CommandSubscribe)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSubscribe
_BaseCommand'subscribe
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSubscribe
y__ -> BaseCommand
x__ {_BaseCommand'subscribe :: Maybe CommandSubscribe
_BaseCommand'subscribe = Maybe CommandSubscribe
y__}))
(Maybe CommandSubscribe -> f (Maybe CommandSubscribe))
-> Maybe CommandSubscribe -> f (Maybe CommandSubscribe)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "producer" CommandProducer where
fieldOf :: Proxy# "producer"
-> (CommandProducer -> f CommandProducer)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandProducer -> f (Maybe CommandProducer))
-> BaseCommand -> f BaseCommand)
-> ((CommandProducer -> f CommandProducer)
-> Maybe CommandProducer -> f (Maybe CommandProducer))
-> (CommandProducer -> f CommandProducer)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandProducer)
-> (BaseCommand -> Maybe CommandProducer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandProducer)
(Maybe CommandProducer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandProducer
_BaseCommand'producer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandProducer
y__ -> BaseCommand
x__ {_BaseCommand'producer :: Maybe CommandProducer
_BaseCommand'producer = Maybe CommandProducer
y__}))
(CommandProducer -> Lens' (Maybe CommandProducer) CommandProducer
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandProducer
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'producer" (Prelude.Maybe CommandProducer) where
fieldOf :: Proxy# "maybe'producer"
-> (Maybe CommandProducer -> f (Maybe CommandProducer))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandProducer -> f (Maybe CommandProducer))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandProducer -> f (Maybe CommandProducer))
-> Maybe CommandProducer -> f (Maybe CommandProducer))
-> (Maybe CommandProducer -> f (Maybe CommandProducer))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandProducer)
-> (BaseCommand -> Maybe CommandProducer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandProducer)
(Maybe CommandProducer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandProducer
_BaseCommand'producer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandProducer
y__ -> BaseCommand
x__ {_BaseCommand'producer :: Maybe CommandProducer
_BaseCommand'producer = Maybe CommandProducer
y__}))
(Maybe CommandProducer -> f (Maybe CommandProducer))
-> Maybe CommandProducer -> f (Maybe CommandProducer)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "send" CommandSend where
fieldOf :: Proxy# "send"
-> (CommandSend -> f CommandSend) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandSend -> f (Maybe CommandSend))
-> BaseCommand -> f BaseCommand)
-> ((CommandSend -> f CommandSend)
-> Maybe CommandSend -> f (Maybe CommandSend))
-> (CommandSend -> f CommandSend)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSend)
-> (BaseCommand -> Maybe CommandSend -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandSend) (Maybe CommandSend)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSend
_BaseCommand'send (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSend
y__ -> BaseCommand
x__ {_BaseCommand'send :: Maybe CommandSend
_BaseCommand'send = Maybe CommandSend
y__}))
(CommandSend -> Lens' (Maybe CommandSend) CommandSend
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSend
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'send" (Prelude.Maybe CommandSend) where
fieldOf :: Proxy# "maybe'send"
-> (Maybe CommandSend -> f (Maybe CommandSend))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSend -> f (Maybe CommandSend))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSend -> f (Maybe CommandSend))
-> Maybe CommandSend -> f (Maybe CommandSend))
-> (Maybe CommandSend -> f (Maybe CommandSend))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSend)
-> (BaseCommand -> Maybe CommandSend -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandSend) (Maybe CommandSend)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSend
_BaseCommand'send (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSend
y__ -> BaseCommand
x__ {_BaseCommand'send :: Maybe CommandSend
_BaseCommand'send = Maybe CommandSend
y__}))
(Maybe CommandSend -> f (Maybe CommandSend))
-> Maybe CommandSend -> f (Maybe CommandSend)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "sendReceipt" CommandSendReceipt where
fieldOf :: Proxy# "sendReceipt"
-> (CommandSendReceipt -> f CommandSendReceipt)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> BaseCommand -> f BaseCommand)
-> ((CommandSendReceipt -> f CommandSendReceipt)
-> Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> (CommandSendReceipt -> f CommandSendReceipt)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSendReceipt)
-> (BaseCommand -> Maybe CommandSendReceipt -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSendReceipt)
(Maybe CommandSendReceipt)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSendReceipt
_BaseCommand'sendReceipt
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSendReceipt
y__ -> BaseCommand
x__ {_BaseCommand'sendReceipt :: Maybe CommandSendReceipt
_BaseCommand'sendReceipt = Maybe CommandSendReceipt
y__}))
(CommandSendReceipt
-> Lens' (Maybe CommandSendReceipt) CommandSendReceipt
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSendReceipt
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'sendReceipt" (Prelude.Maybe CommandSendReceipt) where
fieldOf :: Proxy# "maybe'sendReceipt"
-> (Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> (Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSendReceipt)
-> (BaseCommand -> Maybe CommandSendReceipt -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSendReceipt)
(Maybe CommandSendReceipt)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSendReceipt
_BaseCommand'sendReceipt
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSendReceipt
y__ -> BaseCommand
x__ {_BaseCommand'sendReceipt :: Maybe CommandSendReceipt
_BaseCommand'sendReceipt = Maybe CommandSendReceipt
y__}))
(Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt))
-> Maybe CommandSendReceipt -> f (Maybe CommandSendReceipt)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "sendError" CommandSendError where
fieldOf :: Proxy# "sendError"
-> (CommandSendError -> f CommandSendError)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSendError -> f (Maybe CommandSendError))
-> BaseCommand -> f BaseCommand)
-> ((CommandSendError -> f CommandSendError)
-> Maybe CommandSendError -> f (Maybe CommandSendError))
-> (CommandSendError -> f CommandSendError)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSendError)
-> (BaseCommand -> Maybe CommandSendError -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSendError)
(Maybe CommandSendError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSendError
_BaseCommand'sendError
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSendError
y__ -> BaseCommand
x__ {_BaseCommand'sendError :: Maybe CommandSendError
_BaseCommand'sendError = Maybe CommandSendError
y__}))
(CommandSendError -> Lens' (Maybe CommandSendError) CommandSendError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSendError
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'sendError" (Prelude.Maybe CommandSendError) where
fieldOf :: Proxy# "maybe'sendError"
-> (Maybe CommandSendError -> f (Maybe CommandSendError))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSendError -> f (Maybe CommandSendError))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSendError -> f (Maybe CommandSendError))
-> Maybe CommandSendError -> f (Maybe CommandSendError))
-> (Maybe CommandSendError -> f (Maybe CommandSendError))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSendError)
-> (BaseCommand -> Maybe CommandSendError -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSendError)
(Maybe CommandSendError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSendError
_BaseCommand'sendError
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSendError
y__ -> BaseCommand
x__ {_BaseCommand'sendError :: Maybe CommandSendError
_BaseCommand'sendError = Maybe CommandSendError
y__}))
(Maybe CommandSendError -> f (Maybe CommandSendError))
-> Maybe CommandSendError -> f (Maybe CommandSendError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "message" CommandMessage where
fieldOf :: Proxy# "message"
-> (CommandMessage -> f CommandMessage)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandMessage -> f (Maybe CommandMessage))
-> BaseCommand -> f BaseCommand)
-> ((CommandMessage -> f CommandMessage)
-> Maybe CommandMessage -> f (Maybe CommandMessage))
-> (CommandMessage -> f CommandMessage)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandMessage)
-> (BaseCommand -> Maybe CommandMessage -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandMessage)
(Maybe CommandMessage)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandMessage
_BaseCommand'message
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandMessage
y__ -> BaseCommand
x__ {_BaseCommand'message :: Maybe CommandMessage
_BaseCommand'message = Maybe CommandMessage
y__}))
(CommandMessage -> Lens' (Maybe CommandMessage) CommandMessage
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandMessage
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'message" (Prelude.Maybe CommandMessage) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe CommandMessage -> f (Maybe CommandMessage))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandMessage -> f (Maybe CommandMessage))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandMessage -> f (Maybe CommandMessage))
-> Maybe CommandMessage -> f (Maybe CommandMessage))
-> (Maybe CommandMessage -> f (Maybe CommandMessage))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandMessage)
-> (BaseCommand -> Maybe CommandMessage -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandMessage)
(Maybe CommandMessage)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandMessage
_BaseCommand'message
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandMessage
y__ -> BaseCommand
x__ {_BaseCommand'message :: Maybe CommandMessage
_BaseCommand'message = Maybe CommandMessage
y__}))
(Maybe CommandMessage -> f (Maybe CommandMessage))
-> Maybe CommandMessage -> f (Maybe CommandMessage)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "ack" CommandAck where
fieldOf :: Proxy# "ack"
-> (CommandAck -> f CommandAck) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandAck -> f (Maybe CommandAck))
-> BaseCommand -> f BaseCommand)
-> ((CommandAck -> f CommandAck)
-> Maybe CommandAck -> f (Maybe CommandAck))
-> (CommandAck -> f CommandAck)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAck)
-> (BaseCommand -> Maybe CommandAck -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandAck) (Maybe CommandAck)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAck
_BaseCommand'ack (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAck
y__ -> BaseCommand
x__ {_BaseCommand'ack :: Maybe CommandAck
_BaseCommand'ack = Maybe CommandAck
y__}))
(CommandAck -> Lens' (Maybe CommandAck) CommandAck
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAck
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'ack" (Prelude.Maybe CommandAck) where
fieldOf :: Proxy# "maybe'ack"
-> (Maybe CommandAck -> f (Maybe CommandAck))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAck -> f (Maybe CommandAck))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAck -> f (Maybe CommandAck))
-> Maybe CommandAck -> f (Maybe CommandAck))
-> (Maybe CommandAck -> f (Maybe CommandAck))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAck)
-> (BaseCommand -> Maybe CommandAck -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandAck) (Maybe CommandAck)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAck
_BaseCommand'ack (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAck
y__ -> BaseCommand
x__ {_BaseCommand'ack :: Maybe CommandAck
_BaseCommand'ack = Maybe CommandAck
y__}))
(Maybe CommandAck -> f (Maybe CommandAck))
-> Maybe CommandAck -> f (Maybe CommandAck)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "flow" CommandFlow where
fieldOf :: Proxy# "flow"
-> (CommandFlow -> f CommandFlow) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandFlow -> f (Maybe CommandFlow))
-> BaseCommand -> f BaseCommand)
-> ((CommandFlow -> f CommandFlow)
-> Maybe CommandFlow -> f (Maybe CommandFlow))
-> (CommandFlow -> f CommandFlow)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandFlow)
-> (BaseCommand -> Maybe CommandFlow -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandFlow) (Maybe CommandFlow)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandFlow
_BaseCommand'flow (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandFlow
y__ -> BaseCommand
x__ {_BaseCommand'flow :: Maybe CommandFlow
_BaseCommand'flow = Maybe CommandFlow
y__}))
(CommandFlow -> Lens' (Maybe CommandFlow) CommandFlow
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandFlow
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'flow" (Prelude.Maybe CommandFlow) where
fieldOf :: Proxy# "maybe'flow"
-> (Maybe CommandFlow -> f (Maybe CommandFlow))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandFlow -> f (Maybe CommandFlow))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandFlow -> f (Maybe CommandFlow))
-> Maybe CommandFlow -> f (Maybe CommandFlow))
-> (Maybe CommandFlow -> f (Maybe CommandFlow))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandFlow)
-> (BaseCommand -> Maybe CommandFlow -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandFlow) (Maybe CommandFlow)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandFlow
_BaseCommand'flow (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandFlow
y__ -> BaseCommand
x__ {_BaseCommand'flow :: Maybe CommandFlow
_BaseCommand'flow = Maybe CommandFlow
y__}))
(Maybe CommandFlow -> f (Maybe CommandFlow))
-> Maybe CommandFlow -> f (Maybe CommandFlow)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "unsubscribe" CommandUnsubscribe where
fieldOf :: Proxy# "unsubscribe"
-> (CommandUnsubscribe -> f CommandUnsubscribe)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> BaseCommand -> f BaseCommand)
-> ((CommandUnsubscribe -> f CommandUnsubscribe)
-> Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> (CommandUnsubscribe -> f CommandUnsubscribe)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandUnsubscribe)
-> (BaseCommand -> Maybe CommandUnsubscribe -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandUnsubscribe)
(Maybe CommandUnsubscribe)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandUnsubscribe
_BaseCommand'unsubscribe
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandUnsubscribe
y__ -> BaseCommand
x__ {_BaseCommand'unsubscribe :: Maybe CommandUnsubscribe
_BaseCommand'unsubscribe = Maybe CommandUnsubscribe
y__}))
(CommandUnsubscribe
-> Lens' (Maybe CommandUnsubscribe) CommandUnsubscribe
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandUnsubscribe
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'unsubscribe" (Prelude.Maybe CommandUnsubscribe) where
fieldOf :: Proxy# "maybe'unsubscribe"
-> (Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> (Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandUnsubscribe)
-> (BaseCommand -> Maybe CommandUnsubscribe -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandUnsubscribe)
(Maybe CommandUnsubscribe)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandUnsubscribe
_BaseCommand'unsubscribe
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandUnsubscribe
y__ -> BaseCommand
x__ {_BaseCommand'unsubscribe :: Maybe CommandUnsubscribe
_BaseCommand'unsubscribe = Maybe CommandUnsubscribe
y__}))
(Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe))
-> Maybe CommandUnsubscribe -> f (Maybe CommandUnsubscribe)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "success" CommandSuccess where
fieldOf :: Proxy# "success"
-> (CommandSuccess -> f CommandSuccess)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> BaseCommand -> f BaseCommand)
-> ((CommandSuccess -> f CommandSuccess)
-> Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> (CommandSuccess -> f CommandSuccess)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSuccess)
-> (BaseCommand -> Maybe CommandSuccess -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSuccess)
(Maybe CommandSuccess)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSuccess
_BaseCommand'success
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSuccess
y__ -> BaseCommand
x__ {_BaseCommand'success :: Maybe CommandSuccess
_BaseCommand'success = Maybe CommandSuccess
y__}))
(CommandSuccess -> Lens' (Maybe CommandSuccess) CommandSuccess
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSuccess
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'success" (Prelude.Maybe CommandSuccess) where
fieldOf :: Proxy# "maybe'success"
-> (Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> (Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSuccess)
-> (BaseCommand -> Maybe CommandSuccess -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandSuccess)
(Maybe CommandSuccess)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSuccess
_BaseCommand'success
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSuccess
y__ -> BaseCommand
x__ {_BaseCommand'success :: Maybe CommandSuccess
_BaseCommand'success = Maybe CommandSuccess
y__}))
(Maybe CommandSuccess -> f (Maybe CommandSuccess))
-> Maybe CommandSuccess -> f (Maybe CommandSuccess)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "error" CommandError where
fieldOf :: Proxy# "error"
-> (CommandError -> f CommandError) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandError -> f (Maybe CommandError))
-> BaseCommand -> f BaseCommand)
-> ((CommandError -> f CommandError)
-> Maybe CommandError -> f (Maybe CommandError))
-> (CommandError -> f CommandError)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandError)
-> (BaseCommand -> Maybe CommandError -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandError) (Maybe CommandError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandError
_BaseCommand'error (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandError
y__ -> BaseCommand
x__ {_BaseCommand'error :: Maybe CommandError
_BaseCommand'error = Maybe CommandError
y__}))
(CommandError -> Lens' (Maybe CommandError) CommandError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandError
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'error" (Prelude.Maybe CommandError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe CommandError -> f (Maybe CommandError))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandError -> f (Maybe CommandError))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandError -> f (Maybe CommandError))
-> Maybe CommandError -> f (Maybe CommandError))
-> (Maybe CommandError -> f (Maybe CommandError))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandError)
-> (BaseCommand -> Maybe CommandError -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandError) (Maybe CommandError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandError
_BaseCommand'error (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandError
y__ -> BaseCommand
x__ {_BaseCommand'error :: Maybe CommandError
_BaseCommand'error = Maybe CommandError
y__}))
(Maybe CommandError -> f (Maybe CommandError))
-> Maybe CommandError -> f (Maybe CommandError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "closeProducer" CommandCloseProducer where
fieldOf :: Proxy# "closeProducer"
-> (CommandCloseProducer -> f CommandCloseProducer)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> BaseCommand -> f BaseCommand)
-> ((CommandCloseProducer -> f CommandCloseProducer)
-> Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> (CommandCloseProducer -> f CommandCloseProducer)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandCloseProducer)
-> (BaseCommand -> Maybe CommandCloseProducer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandCloseProducer)
(Maybe CommandCloseProducer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandCloseProducer
_BaseCommand'closeProducer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandCloseProducer
y__ -> BaseCommand
x__ {_BaseCommand'closeProducer :: Maybe CommandCloseProducer
_BaseCommand'closeProducer = Maybe CommandCloseProducer
y__}))
(CommandCloseProducer
-> Lens' (Maybe CommandCloseProducer) CommandCloseProducer
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandCloseProducer
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'closeProducer" (Prelude.Maybe CommandCloseProducer) where
fieldOf :: Proxy# "maybe'closeProducer"
-> (Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> (Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandCloseProducer)
-> (BaseCommand -> Maybe CommandCloseProducer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandCloseProducer)
(Maybe CommandCloseProducer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandCloseProducer
_BaseCommand'closeProducer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandCloseProducer
y__ -> BaseCommand
x__ {_BaseCommand'closeProducer :: Maybe CommandCloseProducer
_BaseCommand'closeProducer = Maybe CommandCloseProducer
y__}))
(Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer))
-> Maybe CommandCloseProducer -> f (Maybe CommandCloseProducer)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "closeConsumer" CommandCloseConsumer where
fieldOf :: Proxy# "closeConsumer"
-> (CommandCloseConsumer -> f CommandCloseConsumer)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> BaseCommand -> f BaseCommand)
-> ((CommandCloseConsumer -> f CommandCloseConsumer)
-> Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> (CommandCloseConsumer -> f CommandCloseConsumer)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandCloseConsumer)
-> (BaseCommand -> Maybe CommandCloseConsumer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandCloseConsumer)
(Maybe CommandCloseConsumer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandCloseConsumer
_BaseCommand'closeConsumer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandCloseConsumer
y__ -> BaseCommand
x__ {_BaseCommand'closeConsumer :: Maybe CommandCloseConsumer
_BaseCommand'closeConsumer = Maybe CommandCloseConsumer
y__}))
(CommandCloseConsumer
-> Lens' (Maybe CommandCloseConsumer) CommandCloseConsumer
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandCloseConsumer
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'closeConsumer" (Prelude.Maybe CommandCloseConsumer) where
fieldOf :: Proxy# "maybe'closeConsumer"
-> (Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> (Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandCloseConsumer)
-> (BaseCommand -> Maybe CommandCloseConsumer -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandCloseConsumer)
(Maybe CommandCloseConsumer)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandCloseConsumer
_BaseCommand'closeConsumer
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandCloseConsumer
y__ -> BaseCommand
x__ {_BaseCommand'closeConsumer :: Maybe CommandCloseConsumer
_BaseCommand'closeConsumer = Maybe CommandCloseConsumer
y__}))
(Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer))
-> Maybe CommandCloseConsumer -> f (Maybe CommandCloseConsumer)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "producerSuccess" CommandProducerSuccess where
fieldOf :: Proxy# "producerSuccess"
-> (CommandProducerSuccess -> f CommandProducerSuccess)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandProducerSuccess -> f (Maybe CommandProducerSuccess))
-> BaseCommand -> f BaseCommand)
-> ((CommandProducerSuccess -> f CommandProducerSuccess)
-> Maybe CommandProducerSuccess
-> f (Maybe CommandProducerSuccess))
-> (CommandProducerSuccess -> f CommandProducerSuccess)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandProducerSuccess)
-> (BaseCommand -> Maybe CommandProducerSuccess -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandProducerSuccess)
(Maybe CommandProducerSuccess)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandProducerSuccess
_BaseCommand'producerSuccess
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandProducerSuccess
y__ -> BaseCommand
x__ {_BaseCommand'producerSuccess :: Maybe CommandProducerSuccess
_BaseCommand'producerSuccess = Maybe CommandProducerSuccess
y__}))
(CommandProducerSuccess
-> Lens' (Maybe CommandProducerSuccess) CommandProducerSuccess
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandProducerSuccess
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'producerSuccess" (Prelude.Maybe CommandProducerSuccess) where
fieldOf :: Proxy# "maybe'producerSuccess"
-> (Maybe CommandProducerSuccess
-> f (Maybe CommandProducerSuccess))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandProducerSuccess -> f (Maybe CommandProducerSuccess))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandProducerSuccess
-> f (Maybe CommandProducerSuccess))
-> Maybe CommandProducerSuccess
-> f (Maybe CommandProducerSuccess))
-> (Maybe CommandProducerSuccess
-> f (Maybe CommandProducerSuccess))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandProducerSuccess)
-> (BaseCommand -> Maybe CommandProducerSuccess -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandProducerSuccess)
(Maybe CommandProducerSuccess)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandProducerSuccess
_BaseCommand'producerSuccess
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandProducerSuccess
y__ -> BaseCommand
x__ {_BaseCommand'producerSuccess :: Maybe CommandProducerSuccess
_BaseCommand'producerSuccess = Maybe CommandProducerSuccess
y__}))
(Maybe CommandProducerSuccess -> f (Maybe CommandProducerSuccess))
-> Maybe CommandProducerSuccess -> f (Maybe CommandProducerSuccess)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "ping" CommandPing where
fieldOf :: Proxy# "ping"
-> (CommandPing -> f CommandPing) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandPing -> f (Maybe CommandPing))
-> BaseCommand -> f BaseCommand)
-> ((CommandPing -> f CommandPing)
-> Maybe CommandPing -> f (Maybe CommandPing))
-> (CommandPing -> f CommandPing)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPing)
-> (BaseCommand -> Maybe CommandPing -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandPing) (Maybe CommandPing)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPing
_BaseCommand'ping (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPing
y__ -> BaseCommand
x__ {_BaseCommand'ping :: Maybe CommandPing
_BaseCommand'ping = Maybe CommandPing
y__}))
(CommandPing -> Lens' (Maybe CommandPing) CommandPing
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandPing
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'ping" (Prelude.Maybe CommandPing) where
fieldOf :: Proxy# "maybe'ping"
-> (Maybe CommandPing -> f (Maybe CommandPing))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPing -> f (Maybe CommandPing))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandPing -> f (Maybe CommandPing))
-> Maybe CommandPing -> f (Maybe CommandPing))
-> (Maybe CommandPing -> f (Maybe CommandPing))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPing)
-> (BaseCommand -> Maybe CommandPing -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandPing) (Maybe CommandPing)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPing
_BaseCommand'ping (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPing
y__ -> BaseCommand
x__ {_BaseCommand'ping :: Maybe CommandPing
_BaseCommand'ping = Maybe CommandPing
y__}))
(Maybe CommandPing -> f (Maybe CommandPing))
-> Maybe CommandPing -> f (Maybe CommandPing)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "pong" CommandPong where
fieldOf :: Proxy# "pong"
-> (CommandPong -> f CommandPong) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandPong -> f (Maybe CommandPong))
-> BaseCommand -> f BaseCommand)
-> ((CommandPong -> f CommandPong)
-> Maybe CommandPong -> f (Maybe CommandPong))
-> (CommandPong -> f CommandPong)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPong)
-> (BaseCommand -> Maybe CommandPong -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandPong) (Maybe CommandPong)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPong
_BaseCommand'pong (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPong
y__ -> BaseCommand
x__ {_BaseCommand'pong :: Maybe CommandPong
_BaseCommand'pong = Maybe CommandPong
y__}))
(CommandPong -> Lens' (Maybe CommandPong) CommandPong
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandPong
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'pong" (Prelude.Maybe CommandPong) where
fieldOf :: Proxy# "maybe'pong"
-> (Maybe CommandPong -> f (Maybe CommandPong))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPong -> f (Maybe CommandPong))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandPong -> f (Maybe CommandPong))
-> Maybe CommandPong -> f (Maybe CommandPong))
-> (Maybe CommandPong -> f (Maybe CommandPong))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPong)
-> (BaseCommand -> Maybe CommandPong -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandPong) (Maybe CommandPong)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPong
_BaseCommand'pong (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPong
y__ -> BaseCommand
x__ {_BaseCommand'pong :: Maybe CommandPong
_BaseCommand'pong = Maybe CommandPong
y__}))
(Maybe CommandPong -> f (Maybe CommandPong))
-> Maybe CommandPong -> f (Maybe CommandPong)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "redeliverUnacknowledgedMessages" CommandRedeliverUnacknowledgedMessages where
fieldOf :: Proxy# "redeliverUnacknowledgedMessages"
-> (CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> BaseCommand -> f BaseCommand)
-> ((CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> (CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages)
-> (BaseCommand
-> Maybe CommandRedeliverUnacknowledgedMessages -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandRedeliverUnacknowledgedMessages)
(Maybe CommandRedeliverUnacknowledgedMessages)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandRedeliverUnacknowledgedMessages
y__
-> BaseCommand
x__ {_BaseCommand'redeliverUnacknowledgedMessages :: Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages = Maybe CommandRedeliverUnacknowledgedMessages
y__}))
(CommandRedeliverUnacknowledgedMessages
-> Lens'
(Maybe CommandRedeliverUnacknowledgedMessages)
CommandRedeliverUnacknowledgedMessages
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandRedeliverUnacknowledgedMessages
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'redeliverUnacknowledgedMessages" (Prelude.Maybe CommandRedeliverUnacknowledgedMessages) where
fieldOf :: Proxy# "maybe'redeliverUnacknowledgedMessages"
-> (Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> (Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages)
-> (BaseCommand
-> Maybe CommandRedeliverUnacknowledgedMessages -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandRedeliverUnacknowledgedMessages)
(Maybe CommandRedeliverUnacknowledgedMessages)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandRedeliverUnacknowledgedMessages
y__
-> BaseCommand
x__ {_BaseCommand'redeliverUnacknowledgedMessages :: Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages = Maybe CommandRedeliverUnacknowledgedMessages
y__}))
(Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages))
-> Maybe CommandRedeliverUnacknowledgedMessages
-> f (Maybe CommandRedeliverUnacknowledgedMessages)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "partitionMetadata" CommandPartitionedTopicMetadata where
fieldOf :: Proxy# "partitionMetadata"
-> (CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> BaseCommand -> f BaseCommand)
-> ((CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> (CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPartitionedTopicMetadata)
-> (BaseCommand
-> Maybe CommandPartitionedTopicMetadata -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadata)
(Maybe CommandPartitionedTopicMetadata)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPartitionedTopicMetadata
y__ -> BaseCommand
x__ {_BaseCommand'partitionMetadata :: Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata = Maybe CommandPartitionedTopicMetadata
y__}))
(CommandPartitionedTopicMetadata
-> Lens'
(Maybe CommandPartitionedTopicMetadata)
CommandPartitionedTopicMetadata
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandPartitionedTopicMetadata
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'partitionMetadata" (Prelude.Maybe CommandPartitionedTopicMetadata) where
fieldOf :: Proxy# "maybe'partitionMetadata"
-> (Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> (Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPartitionedTopicMetadata)
-> (BaseCommand
-> Maybe CommandPartitionedTopicMetadata -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadata)
(Maybe CommandPartitionedTopicMetadata)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPartitionedTopicMetadata
y__ -> BaseCommand
x__ {_BaseCommand'partitionMetadata :: Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata = Maybe CommandPartitionedTopicMetadata
y__}))
(Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata))
-> Maybe CommandPartitionedTopicMetadata
-> f (Maybe CommandPartitionedTopicMetadata)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "partitionMetadataResponse" CommandPartitionedTopicMetadataResponse where
fieldOf :: Proxy# "partitionMetadataResponse"
-> (CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> (CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse)
-> (BaseCommand
-> Maybe CommandPartitionedTopicMetadataResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadataResponse)
(Maybe CommandPartitionedTopicMetadataResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPartitionedTopicMetadataResponse
y__ -> BaseCommand
x__ {_BaseCommand'partitionMetadataResponse :: Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse = Maybe CommandPartitionedTopicMetadataResponse
y__}))
(CommandPartitionedTopicMetadataResponse
-> Lens'
(Maybe CommandPartitionedTopicMetadataResponse)
CommandPartitionedTopicMetadataResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandPartitionedTopicMetadataResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'partitionMetadataResponse" (Prelude.Maybe CommandPartitionedTopicMetadataResponse) where
fieldOf :: Proxy# "maybe'partitionMetadataResponse"
-> (Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> (Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse)
-> (BaseCommand
-> Maybe CommandPartitionedTopicMetadataResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadataResponse)
(Maybe CommandPartitionedTopicMetadataResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandPartitionedTopicMetadataResponse
y__ -> BaseCommand
x__ {_BaseCommand'partitionMetadataResponse :: Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse = Maybe CommandPartitionedTopicMetadataResponse
y__}))
(Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse))
-> Maybe CommandPartitionedTopicMetadataResponse
-> f (Maybe CommandPartitionedTopicMetadataResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "lookupTopic" CommandLookupTopic where
fieldOf :: Proxy# "lookupTopic"
-> (CommandLookupTopic -> f CommandLookupTopic)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> BaseCommand -> f BaseCommand)
-> ((CommandLookupTopic -> f CommandLookupTopic)
-> Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> (CommandLookupTopic -> f CommandLookupTopic)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandLookupTopic)
-> (BaseCommand -> Maybe CommandLookupTopic -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopic)
(Maybe CommandLookupTopic)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandLookupTopic
_BaseCommand'lookupTopic
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandLookupTopic
y__ -> BaseCommand
x__ {_BaseCommand'lookupTopic :: Maybe CommandLookupTopic
_BaseCommand'lookupTopic = Maybe CommandLookupTopic
y__}))
(CommandLookupTopic
-> Lens' (Maybe CommandLookupTopic) CommandLookupTopic
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandLookupTopic
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'lookupTopic" (Prelude.Maybe CommandLookupTopic) where
fieldOf :: Proxy# "maybe'lookupTopic"
-> (Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> (Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandLookupTopic)
-> (BaseCommand -> Maybe CommandLookupTopic -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopic)
(Maybe CommandLookupTopic)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandLookupTopic
_BaseCommand'lookupTopic
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandLookupTopic
y__ -> BaseCommand
x__ {_BaseCommand'lookupTopic :: Maybe CommandLookupTopic
_BaseCommand'lookupTopic = Maybe CommandLookupTopic
y__}))
(Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic))
-> Maybe CommandLookupTopic -> f (Maybe CommandLookupTopic)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "lookupTopicResponse" CommandLookupTopicResponse where
fieldOf :: Proxy# "lookupTopicResponse"
-> (CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> (CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandLookupTopicResponse)
-> (BaseCommand -> Maybe CommandLookupTopicResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopicResponse)
(Maybe CommandLookupTopicResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandLookupTopicResponse
y__ -> BaseCommand
x__ {_BaseCommand'lookupTopicResponse :: Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse = Maybe CommandLookupTopicResponse
y__}))
(CommandLookupTopicResponse
-> Lens'
(Maybe CommandLookupTopicResponse) CommandLookupTopicResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandLookupTopicResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'lookupTopicResponse" (Prelude.Maybe CommandLookupTopicResponse) where
fieldOf :: Proxy# "maybe'lookupTopicResponse"
-> (Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> (Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandLookupTopicResponse)
-> (BaseCommand -> Maybe CommandLookupTopicResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopicResponse)
(Maybe CommandLookupTopicResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandLookupTopicResponse
y__ -> BaseCommand
x__ {_BaseCommand'lookupTopicResponse :: Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse = Maybe CommandLookupTopicResponse
y__}))
(Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse))
-> Maybe CommandLookupTopicResponse
-> f (Maybe CommandLookupTopicResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "consumerStats" CommandConsumerStats where
fieldOf :: Proxy# "consumerStats"
-> (CommandConsumerStats -> f CommandConsumerStats)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> BaseCommand -> f BaseCommand)
-> ((CommandConsumerStats -> f CommandConsumerStats)
-> Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> (CommandConsumerStats -> f CommandConsumerStats)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConsumerStats)
-> (BaseCommand -> Maybe CommandConsumerStats -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStats)
(Maybe CommandConsumerStats)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConsumerStats
_BaseCommand'consumerStats
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConsumerStats
y__ -> BaseCommand
x__ {_BaseCommand'consumerStats :: Maybe CommandConsumerStats
_BaseCommand'consumerStats = Maybe CommandConsumerStats
y__}))
(CommandConsumerStats
-> Lens' (Maybe CommandConsumerStats) CommandConsumerStats
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandConsumerStats
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'consumerStats" (Prelude.Maybe CommandConsumerStats) where
fieldOf :: Proxy# "maybe'consumerStats"
-> (Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> (Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConsumerStats)
-> (BaseCommand -> Maybe CommandConsumerStats -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStats)
(Maybe CommandConsumerStats)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConsumerStats
_BaseCommand'consumerStats
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConsumerStats
y__ -> BaseCommand
x__ {_BaseCommand'consumerStats :: Maybe CommandConsumerStats
_BaseCommand'consumerStats = Maybe CommandConsumerStats
y__}))
(Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats))
-> Maybe CommandConsumerStats -> f (Maybe CommandConsumerStats)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "consumerStatsResponse" CommandConsumerStatsResponse where
fieldOf :: Proxy# "consumerStatsResponse"
-> (CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse)
-> Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> (CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConsumerStatsResponse)
-> (BaseCommand
-> Maybe CommandConsumerStatsResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStatsResponse)
(Maybe CommandConsumerStatsResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConsumerStatsResponse
y__ -> BaseCommand
x__ {_BaseCommand'consumerStatsResponse :: Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse = Maybe CommandConsumerStatsResponse
y__}))
(CommandConsumerStatsResponse
-> Lens'
(Maybe CommandConsumerStatsResponse) CommandConsumerStatsResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandConsumerStatsResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'consumerStatsResponse" (Prelude.Maybe CommandConsumerStatsResponse) where
fieldOf :: Proxy# "maybe'consumerStatsResponse"
-> (Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> (Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandConsumerStatsResponse)
-> (BaseCommand
-> Maybe CommandConsumerStatsResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStatsResponse)
(Maybe CommandConsumerStatsResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandConsumerStatsResponse
y__ -> BaseCommand
x__ {_BaseCommand'consumerStatsResponse :: Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse = Maybe CommandConsumerStatsResponse
y__}))
(Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse))
-> Maybe CommandConsumerStatsResponse
-> f (Maybe CommandConsumerStatsResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "reachedEndOfTopic" CommandReachedEndOfTopic where
fieldOf :: Proxy# "reachedEndOfTopic"
-> (CommandReachedEndOfTopic -> f CommandReachedEndOfTopic)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> BaseCommand -> f BaseCommand)
-> ((CommandReachedEndOfTopic -> f CommandReachedEndOfTopic)
-> Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> (CommandReachedEndOfTopic -> f CommandReachedEndOfTopic)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandReachedEndOfTopic)
-> (BaseCommand -> Maybe CommandReachedEndOfTopic -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandReachedEndOfTopic)
(Maybe CommandReachedEndOfTopic)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandReachedEndOfTopic
y__ -> BaseCommand
x__ {_BaseCommand'reachedEndOfTopic :: Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic = Maybe CommandReachedEndOfTopic
y__}))
(CommandReachedEndOfTopic
-> Lens' (Maybe CommandReachedEndOfTopic) CommandReachedEndOfTopic
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandReachedEndOfTopic
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'reachedEndOfTopic" (Prelude.Maybe CommandReachedEndOfTopic) where
fieldOf :: Proxy# "maybe'reachedEndOfTopic"
-> (Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> (Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandReachedEndOfTopic)
-> (BaseCommand -> Maybe CommandReachedEndOfTopic -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandReachedEndOfTopic)
(Maybe CommandReachedEndOfTopic)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandReachedEndOfTopic
y__ -> BaseCommand
x__ {_BaseCommand'reachedEndOfTopic :: Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic = Maybe CommandReachedEndOfTopic
y__}))
(Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic))
-> Maybe CommandReachedEndOfTopic
-> f (Maybe CommandReachedEndOfTopic)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "seek" CommandSeek where
fieldOf :: Proxy# "seek"
-> (CommandSeek -> f CommandSeek) -> BaseCommand -> f BaseCommand
fieldOf _
= ((Maybe CommandSeek -> f (Maybe CommandSeek))
-> BaseCommand -> f BaseCommand)
-> ((CommandSeek -> f CommandSeek)
-> Maybe CommandSeek -> f (Maybe CommandSeek))
-> (CommandSeek -> f CommandSeek)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSeek)
-> (BaseCommand -> Maybe CommandSeek -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandSeek) (Maybe CommandSeek)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSeek
_BaseCommand'seek (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSeek
y__ -> BaseCommand
x__ {_BaseCommand'seek :: Maybe CommandSeek
_BaseCommand'seek = Maybe CommandSeek
y__}))
(CommandSeek -> Lens' (Maybe CommandSeek) CommandSeek
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSeek
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'seek" (Prelude.Maybe CommandSeek) where
fieldOf :: Proxy# "maybe'seek"
-> (Maybe CommandSeek -> f (Maybe CommandSeek))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandSeek -> f (Maybe CommandSeek))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandSeek -> f (Maybe CommandSeek))
-> Maybe CommandSeek -> f (Maybe CommandSeek))
-> (Maybe CommandSeek -> f (Maybe CommandSeek))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandSeek)
-> (BaseCommand -> Maybe CommandSeek -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandSeek) (Maybe CommandSeek)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandSeek
_BaseCommand'seek (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandSeek
y__ -> BaseCommand
x__ {_BaseCommand'seek :: Maybe CommandSeek
_BaseCommand'seek = Maybe CommandSeek
y__}))
(Maybe CommandSeek -> f (Maybe CommandSeek))
-> Maybe CommandSeek -> f (Maybe CommandSeek)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getLastMessageId" CommandGetLastMessageId where
fieldOf :: Proxy# "getLastMessageId"
-> (CommandGetLastMessageId -> f CommandGetLastMessageId)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetLastMessageId -> f CommandGetLastMessageId)
-> Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> (CommandGetLastMessageId -> f CommandGetLastMessageId)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetLastMessageId)
-> (BaseCommand -> Maybe CommandGetLastMessageId -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageId)
(Maybe CommandGetLastMessageId)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetLastMessageId
y__ -> BaseCommand
x__ {_BaseCommand'getLastMessageId :: Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId = Maybe CommandGetLastMessageId
y__}))
(CommandGetLastMessageId
-> Lens' (Maybe CommandGetLastMessageId) CommandGetLastMessageId
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetLastMessageId
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getLastMessageId" (Prelude.Maybe CommandGetLastMessageId) where
fieldOf :: Proxy# "maybe'getLastMessageId"
-> (Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> (Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetLastMessageId)
-> (BaseCommand -> Maybe CommandGetLastMessageId -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageId)
(Maybe CommandGetLastMessageId)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetLastMessageId
y__ -> BaseCommand
x__ {_BaseCommand'getLastMessageId :: Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId = Maybe CommandGetLastMessageId
y__}))
(Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId))
-> Maybe CommandGetLastMessageId
-> f (Maybe CommandGetLastMessageId)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getLastMessageIdResponse" CommandGetLastMessageIdResponse where
fieldOf :: Proxy# "getLastMessageIdResponse"
-> (CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse)
-> Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> (CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetLastMessageIdResponse)
-> (BaseCommand
-> Maybe CommandGetLastMessageIdResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageIdResponse)
(Maybe CommandGetLastMessageIdResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetLastMessageIdResponse
y__ -> BaseCommand
x__ {_BaseCommand'getLastMessageIdResponse :: Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse = Maybe CommandGetLastMessageIdResponse
y__}))
(CommandGetLastMessageIdResponse
-> Lens'
(Maybe CommandGetLastMessageIdResponse)
CommandGetLastMessageIdResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetLastMessageIdResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getLastMessageIdResponse" (Prelude.Maybe CommandGetLastMessageIdResponse) where
fieldOf :: Proxy# "maybe'getLastMessageIdResponse"
-> (Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> (Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetLastMessageIdResponse)
-> (BaseCommand
-> Maybe CommandGetLastMessageIdResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageIdResponse)
(Maybe CommandGetLastMessageIdResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetLastMessageIdResponse
y__ -> BaseCommand
x__ {_BaseCommand'getLastMessageIdResponse :: Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse = Maybe CommandGetLastMessageIdResponse
y__}))
(Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse))
-> Maybe CommandGetLastMessageIdResponse
-> f (Maybe CommandGetLastMessageIdResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "activeConsumerChange" CommandActiveConsumerChange where
fieldOf :: Proxy# "activeConsumerChange"
-> (CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> BaseCommand -> f BaseCommand)
-> ((CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> (CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandActiveConsumerChange)
-> (BaseCommand
-> Maybe CommandActiveConsumerChange -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandActiveConsumerChange)
(Maybe CommandActiveConsumerChange)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandActiveConsumerChange
y__ -> BaseCommand
x__ {_BaseCommand'activeConsumerChange :: Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange = Maybe CommandActiveConsumerChange
y__}))
(CommandActiveConsumerChange
-> Lens'
(Maybe CommandActiveConsumerChange) CommandActiveConsumerChange
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandActiveConsumerChange
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'activeConsumerChange" (Prelude.Maybe CommandActiveConsumerChange) where
fieldOf :: Proxy# "maybe'activeConsumerChange"
-> (Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> (Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandActiveConsumerChange)
-> (BaseCommand
-> Maybe CommandActiveConsumerChange -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandActiveConsumerChange)
(Maybe CommandActiveConsumerChange)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandActiveConsumerChange
y__ -> BaseCommand
x__ {_BaseCommand'activeConsumerChange :: Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange = Maybe CommandActiveConsumerChange
y__}))
(Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange))
-> Maybe CommandActiveConsumerChange
-> f (Maybe CommandActiveConsumerChange)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getTopicsOfNamespace" CommandGetTopicsOfNamespace where
fieldOf :: Proxy# "getTopicsOfNamespace"
-> (CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> (CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetTopicsOfNamespace)
-> (BaseCommand
-> Maybe CommandGetTopicsOfNamespace -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespace)
(Maybe CommandGetTopicsOfNamespace)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetTopicsOfNamespace
y__ -> BaseCommand
x__ {_BaseCommand'getTopicsOfNamespace :: Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace = Maybe CommandGetTopicsOfNamespace
y__}))
(CommandGetTopicsOfNamespace
-> Lens'
(Maybe CommandGetTopicsOfNamespace) CommandGetTopicsOfNamespace
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetTopicsOfNamespace
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getTopicsOfNamespace" (Prelude.Maybe CommandGetTopicsOfNamespace) where
fieldOf :: Proxy# "maybe'getTopicsOfNamespace"
-> (Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> (Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetTopicsOfNamespace)
-> (BaseCommand
-> Maybe CommandGetTopicsOfNamespace -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespace)
(Maybe CommandGetTopicsOfNamespace)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetTopicsOfNamespace
y__ -> BaseCommand
x__ {_BaseCommand'getTopicsOfNamespace :: Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace = Maybe CommandGetTopicsOfNamespace
y__}))
(Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace))
-> Maybe CommandGetTopicsOfNamespace
-> f (Maybe CommandGetTopicsOfNamespace)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getTopicsOfNamespaceResponse" CommandGetTopicsOfNamespaceResponse where
fieldOf :: Proxy# "getTopicsOfNamespaceResponse"
-> (CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> (CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse)
-> (BaseCommand
-> Maybe CommandGetTopicsOfNamespaceResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespaceResponse)
(Maybe CommandGetTopicsOfNamespaceResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetTopicsOfNamespaceResponse
y__
-> BaseCommand
x__ {_BaseCommand'getTopicsOfNamespaceResponse :: Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse = Maybe CommandGetTopicsOfNamespaceResponse
y__}))
(CommandGetTopicsOfNamespaceResponse
-> Lens'
(Maybe CommandGetTopicsOfNamespaceResponse)
CommandGetTopicsOfNamespaceResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetTopicsOfNamespaceResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getTopicsOfNamespaceResponse" (Prelude.Maybe CommandGetTopicsOfNamespaceResponse) where
fieldOf :: Proxy# "maybe'getTopicsOfNamespaceResponse"
-> (Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> (Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse)
-> (BaseCommand
-> Maybe CommandGetTopicsOfNamespaceResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespaceResponse)
(Maybe CommandGetTopicsOfNamespaceResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetTopicsOfNamespaceResponse
y__
-> BaseCommand
x__ {_BaseCommand'getTopicsOfNamespaceResponse :: Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse = Maybe CommandGetTopicsOfNamespaceResponse
y__}))
(Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse))
-> Maybe CommandGetTopicsOfNamespaceResponse
-> f (Maybe CommandGetTopicsOfNamespaceResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getSchema" CommandGetSchema where
fieldOf :: Proxy# "getSchema"
-> (CommandGetSchema -> f CommandGetSchema)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetSchema -> f CommandGetSchema)
-> Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> (CommandGetSchema -> f CommandGetSchema)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetSchema)
-> (BaseCommand -> Maybe CommandGetSchema -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchema)
(Maybe CommandGetSchema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetSchema
_BaseCommand'getSchema
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetSchema
y__ -> BaseCommand
x__ {_BaseCommand'getSchema :: Maybe CommandGetSchema
_BaseCommand'getSchema = Maybe CommandGetSchema
y__}))
(CommandGetSchema -> Lens' (Maybe CommandGetSchema) CommandGetSchema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetSchema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getSchema" (Prelude.Maybe CommandGetSchema) where
fieldOf :: Proxy# "maybe'getSchema"
-> (Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> (Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetSchema)
-> (BaseCommand -> Maybe CommandGetSchema -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchema)
(Maybe CommandGetSchema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetSchema
_BaseCommand'getSchema
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetSchema
y__ -> BaseCommand
x__ {_BaseCommand'getSchema :: Maybe CommandGetSchema
_BaseCommand'getSchema = Maybe CommandGetSchema
y__}))
(Maybe CommandGetSchema -> f (Maybe CommandGetSchema))
-> Maybe CommandGetSchema -> f (Maybe CommandGetSchema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getSchemaResponse" CommandGetSchemaResponse where
fieldOf :: Proxy# "getSchemaResponse"
-> (CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> (CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetSchemaResponse)
-> (BaseCommand -> Maybe CommandGetSchemaResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchemaResponse)
(Maybe CommandGetSchemaResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetSchemaResponse
y__ -> BaseCommand
x__ {_BaseCommand'getSchemaResponse :: Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse = Maybe CommandGetSchemaResponse
y__}))
(CommandGetSchemaResponse
-> Lens' (Maybe CommandGetSchemaResponse) CommandGetSchemaResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetSchemaResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getSchemaResponse" (Prelude.Maybe CommandGetSchemaResponse) where
fieldOf :: Proxy# "maybe'getSchemaResponse"
-> (Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> (Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetSchemaResponse)
-> (BaseCommand -> Maybe CommandGetSchemaResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchemaResponse)
(Maybe CommandGetSchemaResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetSchemaResponse
y__ -> BaseCommand
x__ {_BaseCommand'getSchemaResponse :: Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse = Maybe CommandGetSchemaResponse
y__}))
(Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse))
-> Maybe CommandGetSchemaResponse
-> f (Maybe CommandGetSchemaResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "authChallenge" CommandAuthChallenge where
fieldOf :: Proxy# "authChallenge"
-> (CommandAuthChallenge -> f CommandAuthChallenge)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> BaseCommand -> f BaseCommand)
-> ((CommandAuthChallenge -> f CommandAuthChallenge)
-> Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> (CommandAuthChallenge -> f CommandAuthChallenge)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAuthChallenge)
-> (BaseCommand -> Maybe CommandAuthChallenge -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAuthChallenge)
(Maybe CommandAuthChallenge)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAuthChallenge
_BaseCommand'authChallenge
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAuthChallenge
y__ -> BaseCommand
x__ {_BaseCommand'authChallenge :: Maybe CommandAuthChallenge
_BaseCommand'authChallenge = Maybe CommandAuthChallenge
y__}))
(CommandAuthChallenge
-> Lens' (Maybe CommandAuthChallenge) CommandAuthChallenge
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAuthChallenge
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'authChallenge" (Prelude.Maybe CommandAuthChallenge) where
fieldOf :: Proxy# "maybe'authChallenge"
-> (Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> (Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAuthChallenge)
-> (BaseCommand -> Maybe CommandAuthChallenge -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAuthChallenge)
(Maybe CommandAuthChallenge)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAuthChallenge
_BaseCommand'authChallenge
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAuthChallenge
y__ -> BaseCommand
x__ {_BaseCommand'authChallenge :: Maybe CommandAuthChallenge
_BaseCommand'authChallenge = Maybe CommandAuthChallenge
y__}))
(Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge))
-> Maybe CommandAuthChallenge -> f (Maybe CommandAuthChallenge)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "authResponse" CommandAuthResponse where
fieldOf :: Proxy# "authResponse"
-> (CommandAuthResponse -> f CommandAuthResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandAuthResponse -> f CommandAuthResponse)
-> Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> (CommandAuthResponse -> f CommandAuthResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAuthResponse)
-> (BaseCommand -> Maybe CommandAuthResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAuthResponse)
(Maybe CommandAuthResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAuthResponse
_BaseCommand'authResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAuthResponse
y__ -> BaseCommand
x__ {_BaseCommand'authResponse :: Maybe CommandAuthResponse
_BaseCommand'authResponse = Maybe CommandAuthResponse
y__}))
(CommandAuthResponse
-> Lens' (Maybe CommandAuthResponse) CommandAuthResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAuthResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'authResponse" (Prelude.Maybe CommandAuthResponse) where
fieldOf :: Proxy# "maybe'authResponse"
-> (Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> (Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAuthResponse)
-> (BaseCommand -> Maybe CommandAuthResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAuthResponse)
(Maybe CommandAuthResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAuthResponse
_BaseCommand'authResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAuthResponse
y__ -> BaseCommand
x__ {_BaseCommand'authResponse :: Maybe CommandAuthResponse
_BaseCommand'authResponse = Maybe CommandAuthResponse
y__}))
(Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse))
-> Maybe CommandAuthResponse -> f (Maybe CommandAuthResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "ackResponse" CommandAckResponse where
fieldOf :: Proxy# "ackResponse"
-> (CommandAckResponse -> f CommandAckResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandAckResponse -> f CommandAckResponse)
-> Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> (CommandAckResponse -> f CommandAckResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAckResponse)
-> (BaseCommand -> Maybe CommandAckResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAckResponse)
(Maybe CommandAckResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAckResponse
_BaseCommand'ackResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAckResponse
y__ -> BaseCommand
x__ {_BaseCommand'ackResponse :: Maybe CommandAckResponse
_BaseCommand'ackResponse = Maybe CommandAckResponse
y__}))
(CommandAckResponse
-> Lens' (Maybe CommandAckResponse) CommandAckResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAckResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'ackResponse" (Prelude.Maybe CommandAckResponse) where
fieldOf :: Proxy# "maybe'ackResponse"
-> (Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> (Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAckResponse)
-> (BaseCommand -> Maybe CommandAckResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAckResponse)
(Maybe CommandAckResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAckResponse
_BaseCommand'ackResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAckResponse
y__ -> BaseCommand
x__ {_BaseCommand'ackResponse :: Maybe CommandAckResponse
_BaseCommand'ackResponse = Maybe CommandAckResponse
y__}))
(Maybe CommandAckResponse -> f (Maybe CommandAckResponse))
-> Maybe CommandAckResponse -> f (Maybe CommandAckResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getOrCreateSchema" CommandGetOrCreateSchema where
fieldOf :: Proxy# "getOrCreateSchema"
-> (CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> (CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetOrCreateSchema)
-> (BaseCommand -> Maybe CommandGetOrCreateSchema -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchema)
(Maybe CommandGetOrCreateSchema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetOrCreateSchema
y__ -> BaseCommand
x__ {_BaseCommand'getOrCreateSchema :: Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema = Maybe CommandGetOrCreateSchema
y__}))
(CommandGetOrCreateSchema
-> Lens' (Maybe CommandGetOrCreateSchema) CommandGetOrCreateSchema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetOrCreateSchema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getOrCreateSchema" (Prelude.Maybe CommandGetOrCreateSchema) where
fieldOf :: Proxy# "maybe'getOrCreateSchema"
-> (Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> (Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetOrCreateSchema)
-> (BaseCommand -> Maybe CommandGetOrCreateSchema -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchema)
(Maybe CommandGetOrCreateSchema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetOrCreateSchema
y__ -> BaseCommand
x__ {_BaseCommand'getOrCreateSchema :: Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema = Maybe CommandGetOrCreateSchema
y__}))
(Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema))
-> Maybe CommandGetOrCreateSchema
-> f (Maybe CommandGetOrCreateSchema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "getOrCreateSchemaResponse" CommandGetOrCreateSchemaResponse where
fieldOf :: Proxy# "getOrCreateSchemaResponse"
-> (CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> (CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetOrCreateSchemaResponse)
-> (BaseCommand
-> Maybe CommandGetOrCreateSchemaResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchemaResponse)
(Maybe CommandGetOrCreateSchemaResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetOrCreateSchemaResponse
y__ -> BaseCommand
x__ {_BaseCommand'getOrCreateSchemaResponse :: Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse = Maybe CommandGetOrCreateSchemaResponse
y__}))
(CommandGetOrCreateSchemaResponse
-> Lens'
(Maybe CommandGetOrCreateSchemaResponse)
CommandGetOrCreateSchemaResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetOrCreateSchemaResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'getOrCreateSchemaResponse" (Prelude.Maybe CommandGetOrCreateSchemaResponse) where
fieldOf :: Proxy# "maybe'getOrCreateSchemaResponse"
-> (Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> (Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandGetOrCreateSchemaResponse)
-> (BaseCommand
-> Maybe CommandGetOrCreateSchemaResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchemaResponse)
(Maybe CommandGetOrCreateSchemaResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandGetOrCreateSchemaResponse
y__ -> BaseCommand
x__ {_BaseCommand'getOrCreateSchemaResponse :: Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse = Maybe CommandGetOrCreateSchemaResponse
y__}))
(Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse))
-> Maybe CommandGetOrCreateSchemaResponse
-> f (Maybe CommandGetOrCreateSchemaResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "newTxn" CommandNewTxn where
fieldOf :: Proxy# "newTxn"
-> (CommandNewTxn -> f CommandNewTxn)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> BaseCommand -> f BaseCommand)
-> ((CommandNewTxn -> f CommandNewTxn)
-> Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> (CommandNewTxn -> f CommandNewTxn)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandNewTxn)
-> (BaseCommand -> Maybe CommandNewTxn -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandNewTxn) (Maybe CommandNewTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandNewTxn
_BaseCommand'newTxn (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandNewTxn
y__ -> BaseCommand
x__ {_BaseCommand'newTxn :: Maybe CommandNewTxn
_BaseCommand'newTxn = Maybe CommandNewTxn
y__}))
(CommandNewTxn -> Lens' (Maybe CommandNewTxn) CommandNewTxn
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandNewTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'newTxn" (Prelude.Maybe CommandNewTxn) where
fieldOf :: Proxy# "maybe'newTxn"
-> (Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> (Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandNewTxn)
-> (BaseCommand -> Maybe CommandNewTxn -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandNewTxn) (Maybe CommandNewTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandNewTxn
_BaseCommand'newTxn (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandNewTxn
y__ -> BaseCommand
x__ {_BaseCommand'newTxn :: Maybe CommandNewTxn
_BaseCommand'newTxn = Maybe CommandNewTxn
y__}))
(Maybe CommandNewTxn -> f (Maybe CommandNewTxn))
-> Maybe CommandNewTxn -> f (Maybe CommandNewTxn)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "newTxnResponse" CommandNewTxnResponse where
fieldOf :: Proxy# "newTxnResponse"
-> (CommandNewTxnResponse -> f CommandNewTxnResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandNewTxnResponse -> f CommandNewTxnResponse)
-> Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> (CommandNewTxnResponse -> f CommandNewTxnResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandNewTxnResponse)
-> (BaseCommand -> Maybe CommandNewTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandNewTxnResponse)
(Maybe CommandNewTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandNewTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'newTxnResponse :: Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse = Maybe CommandNewTxnResponse
y__}))
(CommandNewTxnResponse
-> Lens' (Maybe CommandNewTxnResponse) CommandNewTxnResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandNewTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'newTxnResponse" (Prelude.Maybe CommandNewTxnResponse) where
fieldOf :: Proxy# "maybe'newTxnResponse"
-> (Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandNewTxnResponse
-> f (Maybe CommandNewTxnResponse))
-> Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> (Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandNewTxnResponse)
-> (BaseCommand -> Maybe CommandNewTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandNewTxnResponse)
(Maybe CommandNewTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandNewTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'newTxnResponse :: Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse = Maybe CommandNewTxnResponse
y__}))
(Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse))
-> Maybe CommandNewTxnResponse -> f (Maybe CommandNewTxnResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "addPartitionToTxn" CommandAddPartitionToTxn where
fieldOf :: Proxy# "addPartitionToTxn"
-> (CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> BaseCommand -> f BaseCommand)
-> ((CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> (CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddPartitionToTxn)
-> (BaseCommand -> Maybe CommandAddPartitionToTxn -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxn)
(Maybe CommandAddPartitionToTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddPartitionToTxn
y__ -> BaseCommand
x__ {_BaseCommand'addPartitionToTxn :: Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn = Maybe CommandAddPartitionToTxn
y__}))
(CommandAddPartitionToTxn
-> Lens' (Maybe CommandAddPartitionToTxn) CommandAddPartitionToTxn
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAddPartitionToTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'addPartitionToTxn" (Prelude.Maybe CommandAddPartitionToTxn) where
fieldOf :: Proxy# "maybe'addPartitionToTxn"
-> (Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> (Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddPartitionToTxn)
-> (BaseCommand -> Maybe CommandAddPartitionToTxn -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxn)
(Maybe CommandAddPartitionToTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddPartitionToTxn
y__ -> BaseCommand
x__ {_BaseCommand'addPartitionToTxn :: Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn = Maybe CommandAddPartitionToTxn
y__}))
(Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn))
-> Maybe CommandAddPartitionToTxn
-> f (Maybe CommandAddPartitionToTxn)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "addPartitionToTxnResponse" CommandAddPartitionToTxnResponse where
fieldOf :: Proxy# "addPartitionToTxnResponse"
-> (CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> (CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddPartitionToTxnResponse)
-> (BaseCommand
-> Maybe CommandAddPartitionToTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxnResponse)
(Maybe CommandAddPartitionToTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddPartitionToTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'addPartitionToTxnResponse :: Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse = Maybe CommandAddPartitionToTxnResponse
y__}))
(CommandAddPartitionToTxnResponse
-> Lens'
(Maybe CommandAddPartitionToTxnResponse)
CommandAddPartitionToTxnResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAddPartitionToTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'addPartitionToTxnResponse" (Prelude.Maybe CommandAddPartitionToTxnResponse) where
fieldOf :: Proxy# "maybe'addPartitionToTxnResponse"
-> (Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> (Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddPartitionToTxnResponse)
-> (BaseCommand
-> Maybe CommandAddPartitionToTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxnResponse)
(Maybe CommandAddPartitionToTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddPartitionToTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'addPartitionToTxnResponse :: Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse = Maybe CommandAddPartitionToTxnResponse
y__}))
(Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse))
-> Maybe CommandAddPartitionToTxnResponse
-> f (Maybe CommandAddPartitionToTxnResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "addSubscriptionToTxn" CommandAddSubscriptionToTxn where
fieldOf :: Proxy# "addSubscriptionToTxn"
-> (CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> BaseCommand -> f BaseCommand)
-> ((CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> (CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddSubscriptionToTxn)
-> (BaseCommand
-> Maybe CommandAddSubscriptionToTxn -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxn)
(Maybe CommandAddSubscriptionToTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddSubscriptionToTxn
y__ -> BaseCommand
x__ {_BaseCommand'addSubscriptionToTxn :: Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn = Maybe CommandAddSubscriptionToTxn
y__}))
(CommandAddSubscriptionToTxn
-> Lens'
(Maybe CommandAddSubscriptionToTxn) CommandAddSubscriptionToTxn
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAddSubscriptionToTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'addSubscriptionToTxn" (Prelude.Maybe CommandAddSubscriptionToTxn) where
fieldOf :: Proxy# "maybe'addSubscriptionToTxn"
-> (Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> (Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddSubscriptionToTxn)
-> (BaseCommand
-> Maybe CommandAddSubscriptionToTxn -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxn)
(Maybe CommandAddSubscriptionToTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddSubscriptionToTxn
y__ -> BaseCommand
x__ {_BaseCommand'addSubscriptionToTxn :: Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn = Maybe CommandAddSubscriptionToTxn
y__}))
(Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn))
-> Maybe CommandAddSubscriptionToTxn
-> f (Maybe CommandAddSubscriptionToTxn)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "addSubscriptionToTxnResponse" CommandAddSubscriptionToTxnResponse where
fieldOf :: Proxy# "addSubscriptionToTxnResponse"
-> (CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> (CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse)
-> (BaseCommand
-> Maybe CommandAddSubscriptionToTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxnResponse)
(Maybe CommandAddSubscriptionToTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddSubscriptionToTxnResponse
y__
-> BaseCommand
x__ {_BaseCommand'addSubscriptionToTxnResponse :: Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse = Maybe CommandAddSubscriptionToTxnResponse
y__}))
(CommandAddSubscriptionToTxnResponse
-> Lens'
(Maybe CommandAddSubscriptionToTxnResponse)
CommandAddSubscriptionToTxnResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAddSubscriptionToTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'addSubscriptionToTxnResponse" (Prelude.Maybe CommandAddSubscriptionToTxnResponse) where
fieldOf :: Proxy# "maybe'addSubscriptionToTxnResponse"
-> (Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> (Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse)
-> (BaseCommand
-> Maybe CommandAddSubscriptionToTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxnResponse)
(Maybe CommandAddSubscriptionToTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandAddSubscriptionToTxnResponse
y__
-> BaseCommand
x__ {_BaseCommand'addSubscriptionToTxnResponse :: Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse = Maybe CommandAddSubscriptionToTxnResponse
y__}))
(Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse))
-> Maybe CommandAddSubscriptionToTxnResponse
-> f (Maybe CommandAddSubscriptionToTxnResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxn" CommandEndTxn where
fieldOf :: Proxy# "endTxn"
-> (CommandEndTxn -> f CommandEndTxn)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxn -> f CommandEndTxn)
-> Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> (CommandEndTxn -> f CommandEndTxn)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxn)
-> (BaseCommand -> Maybe CommandEndTxn -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandEndTxn) (Maybe CommandEndTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxn
_BaseCommand'endTxn (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxn
y__ -> BaseCommand
x__ {_BaseCommand'endTxn :: Maybe CommandEndTxn
_BaseCommand'endTxn = Maybe CommandEndTxn
y__}))
(CommandEndTxn -> Lens' (Maybe CommandEndTxn) CommandEndTxn
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxn" (Prelude.Maybe CommandEndTxn) where
fieldOf :: Proxy# "maybe'endTxn"
-> (Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> (Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxn)
-> (BaseCommand -> Maybe CommandEndTxn -> BaseCommand)
-> Lens
BaseCommand BaseCommand (Maybe CommandEndTxn) (Maybe CommandEndTxn)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxn
_BaseCommand'endTxn (\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxn
y__ -> BaseCommand
x__ {_BaseCommand'endTxn :: Maybe CommandEndTxn
_BaseCommand'endTxn = Maybe CommandEndTxn
y__}))
(Maybe CommandEndTxn -> f (Maybe CommandEndTxn))
-> Maybe CommandEndTxn -> f (Maybe CommandEndTxn)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxnResponse" CommandEndTxnResponse where
fieldOf :: Proxy# "endTxnResponse"
-> (CommandEndTxnResponse -> f CommandEndTxnResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxnResponse -> f CommandEndTxnResponse)
-> Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> (CommandEndTxnResponse -> f CommandEndTxnResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnResponse)
-> (BaseCommand -> Maybe CommandEndTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnResponse)
(Maybe CommandEndTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'endTxnResponse :: Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse = Maybe CommandEndTxnResponse
y__}))
(CommandEndTxnResponse
-> Lens' (Maybe CommandEndTxnResponse) CommandEndTxnResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxnResponse" (Prelude.Maybe CommandEndTxnResponse) where
fieldOf :: Proxy# "maybe'endTxnResponse"
-> (Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxnResponse
-> f (Maybe CommandEndTxnResponse))
-> Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> (Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnResponse)
-> (BaseCommand -> Maybe CommandEndTxnResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnResponse)
(Maybe CommandEndTxnResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnResponse
y__ -> BaseCommand
x__ {_BaseCommand'endTxnResponse :: Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse = Maybe CommandEndTxnResponse
y__}))
(Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse))
-> Maybe CommandEndTxnResponse -> f (Maybe CommandEndTxnResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxnOnPartition" CommandEndTxnOnPartition where
fieldOf :: Proxy# "endTxnOnPartition"
-> (CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> (CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnPartition)
-> (BaseCommand -> Maybe CommandEndTxnOnPartition -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartition)
(Maybe CommandEndTxnOnPartition)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnPartition
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnPartition :: Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition = Maybe CommandEndTxnOnPartition
y__}))
(CommandEndTxnOnPartition
-> Lens' (Maybe CommandEndTxnOnPartition) CommandEndTxnOnPartition
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxnOnPartition
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxnOnPartition" (Prelude.Maybe CommandEndTxnOnPartition) where
fieldOf :: Proxy# "maybe'endTxnOnPartition"
-> (Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> (Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnPartition)
-> (BaseCommand -> Maybe CommandEndTxnOnPartition -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartition)
(Maybe CommandEndTxnOnPartition)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnPartition
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnPartition :: Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition = Maybe CommandEndTxnOnPartition
y__}))
(Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition))
-> Maybe CommandEndTxnOnPartition
-> f (Maybe CommandEndTxnOnPartition)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxnOnPartitionResponse" CommandEndTxnOnPartitionResponse where
fieldOf :: Proxy# "endTxnOnPartitionResponse"
-> (CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> (CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnPartitionResponse)
-> (BaseCommand
-> Maybe CommandEndTxnOnPartitionResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartitionResponse)
(Maybe CommandEndTxnOnPartitionResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnPartitionResponse
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnPartitionResponse :: Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse = Maybe CommandEndTxnOnPartitionResponse
y__}))
(CommandEndTxnOnPartitionResponse
-> Lens'
(Maybe CommandEndTxnOnPartitionResponse)
CommandEndTxnOnPartitionResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxnOnPartitionResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxnOnPartitionResponse" (Prelude.Maybe CommandEndTxnOnPartitionResponse) where
fieldOf :: Proxy# "maybe'endTxnOnPartitionResponse"
-> (Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> (Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnPartitionResponse)
-> (BaseCommand
-> Maybe CommandEndTxnOnPartitionResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartitionResponse)
(Maybe CommandEndTxnOnPartitionResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnPartitionResponse
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnPartitionResponse :: Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse = Maybe CommandEndTxnOnPartitionResponse
y__}))
(Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse))
-> Maybe CommandEndTxnOnPartitionResponse
-> f (Maybe CommandEndTxnOnPartitionResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxnOnSubscription" CommandEndTxnOnSubscription where
fieldOf :: Proxy# "endTxnOnSubscription"
-> (CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> (CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnSubscription)
-> (BaseCommand
-> Maybe CommandEndTxnOnSubscription -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscription)
(Maybe CommandEndTxnOnSubscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnSubscription
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnSubscription :: Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription = Maybe CommandEndTxnOnSubscription
y__}))
(CommandEndTxnOnSubscription
-> Lens'
(Maybe CommandEndTxnOnSubscription) CommandEndTxnOnSubscription
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxnOnSubscription
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxnOnSubscription" (Prelude.Maybe CommandEndTxnOnSubscription) where
fieldOf :: Proxy# "maybe'endTxnOnSubscription"
-> (Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> (Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnSubscription)
-> (BaseCommand
-> Maybe CommandEndTxnOnSubscription -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscription)
(Maybe CommandEndTxnOnSubscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnSubscription
y__ -> BaseCommand
x__ {_BaseCommand'endTxnOnSubscription :: Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription = Maybe CommandEndTxnOnSubscription
y__}))
(Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription))
-> Maybe CommandEndTxnOnSubscription
-> f (Maybe CommandEndTxnOnSubscription)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BaseCommand "endTxnOnSubscriptionResponse" CommandEndTxnOnSubscriptionResponse where
fieldOf :: Proxy# "endTxnOnSubscriptionResponse"
-> (CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> BaseCommand -> f BaseCommand)
-> ((CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> (CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse)
-> (BaseCommand
-> Maybe CommandEndTxnOnSubscriptionResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscriptionResponse)
(Maybe CommandEndTxnOnSubscriptionResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnSubscriptionResponse
y__
-> BaseCommand
x__ {_BaseCommand'endTxnOnSubscriptionResponse :: Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse = Maybe CommandEndTxnOnSubscriptionResponse
y__}))
(CommandEndTxnOnSubscriptionResponse
-> Lens'
(Maybe CommandEndTxnOnSubscriptionResponse)
CommandEndTxnOnSubscriptionResponse
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandEndTxnOnSubscriptionResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField BaseCommand "maybe'endTxnOnSubscriptionResponse" (Prelude.Maybe CommandEndTxnOnSubscriptionResponse) where
fieldOf :: Proxy# "maybe'endTxnOnSubscriptionResponse"
-> (Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> BaseCommand
-> f BaseCommand
fieldOf _
= ((Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> BaseCommand -> f BaseCommand)
-> ((Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> (Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> BaseCommand
-> f BaseCommand
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse)
-> (BaseCommand
-> Maybe CommandEndTxnOnSubscriptionResponse -> BaseCommand)
-> Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscriptionResponse)
(Maybe CommandEndTxnOnSubscriptionResponse)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse
(\ x__ :: BaseCommand
x__ y__ :: Maybe CommandEndTxnOnSubscriptionResponse
y__
-> BaseCommand
x__ {_BaseCommand'endTxnOnSubscriptionResponse :: Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse = Maybe CommandEndTxnOnSubscriptionResponse
y__}))
(Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse))
-> Maybe CommandEndTxnOnSubscriptionResponse
-> f (Maybe CommandEndTxnOnSubscriptionResponse)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message BaseCommand where
messageName :: Proxy BaseCommand -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.BaseCommand"
packedMessageDescriptor :: Proxy BaseCommand -> ByteString
packedMessageDescriptor _
= "\n\
\\vBaseCommand\DC22\n\
\\EOTtype\CAN\SOH \STX(\SO2\RS.pulsar.proto.BaseCommand.TypeR\EOTtype\DC26\n\
\\aconnect\CAN\STX \SOH(\v2\FS.pulsar.proto.CommandConnectR\aconnect\DC2<\n\
\\tconnected\CAN\ETX \SOH(\v2\RS.pulsar.proto.CommandConnectedR\tconnected\DC2<\n\
\\tsubscribe\CAN\EOT \SOH(\v2\RS.pulsar.proto.CommandSubscribeR\tsubscribe\DC29\n\
\\bproducer\CAN\ENQ \SOH(\v2\GS.pulsar.proto.CommandProducerR\bproducer\DC2-\n\
\\EOTsend\CAN\ACK \SOH(\v2\EM.pulsar.proto.CommandSendR\EOTsend\DC2C\n\
\\fsend_receipt\CAN\a \SOH(\v2 .pulsar.proto.CommandSendReceiptR\vsendReceipt\DC2=\n\
\\n\
\send_error\CAN\b \SOH(\v2\RS.pulsar.proto.CommandSendErrorR\tsendError\DC26\n\
\\amessage\CAN\t \SOH(\v2\FS.pulsar.proto.CommandMessageR\amessage\DC2*\n\
\\ETXack\CAN\n\
\ \SOH(\v2\CAN.pulsar.proto.CommandAckR\ETXack\DC2-\n\
\\EOTflow\CAN\v \SOH(\v2\EM.pulsar.proto.CommandFlowR\EOTflow\DC2B\n\
\\vunsubscribe\CAN\f \SOH(\v2 .pulsar.proto.CommandUnsubscribeR\vunsubscribe\DC26\n\
\\asuccess\CAN\r \SOH(\v2\FS.pulsar.proto.CommandSuccessR\asuccess\DC20\n\
\\ENQerror\CAN\SO \SOH(\v2\SUB.pulsar.proto.CommandErrorR\ENQerror\DC2I\n\
\\SOclose_producer\CAN\SI \SOH(\v2\".pulsar.proto.CommandCloseProducerR\rcloseProducer\DC2I\n\
\\SOclose_consumer\CAN\DLE \SOH(\v2\".pulsar.proto.CommandCloseConsumerR\rcloseConsumer\DC2O\n\
\\DLEproducer_success\CAN\DC1 \SOH(\v2$.pulsar.proto.CommandProducerSuccessR\SIproducerSuccess\DC2-\n\
\\EOTping\CAN\DC2 \SOH(\v2\EM.pulsar.proto.CommandPingR\EOTping\DC2-\n\
\\EOTpong\CAN\DC3 \SOH(\v2\EM.pulsar.proto.CommandPongR\EOTpong\DC2~\n\
\\USredeliverUnacknowledgedMessages\CAN\DC4 \SOH(\v24.pulsar.proto.CommandRedeliverUnacknowledgedMessagesR\USredeliverUnacknowledgedMessages\DC2[\n\
\\DC1partitionMetadata\CAN\NAK \SOH(\v2-.pulsar.proto.CommandPartitionedTopicMetadataR\DC1partitionMetadata\DC2s\n\
\\EMpartitionMetadataResponse\CAN\SYN \SOH(\v25.pulsar.proto.CommandPartitionedTopicMetadataResponseR\EMpartitionMetadataResponse\DC2B\n\
\\vlookupTopic\CAN\ETB \SOH(\v2 .pulsar.proto.CommandLookupTopicR\vlookupTopic\DC2Z\n\
\\DC3lookupTopicResponse\CAN\CAN \SOH(\v2(.pulsar.proto.CommandLookupTopicResponseR\DC3lookupTopicResponse\DC2H\n\
\\rconsumerStats\CAN\EM \SOH(\v2\".pulsar.proto.CommandConsumerStatsR\rconsumerStats\DC2`\n\
\\NAKconsumerStatsResponse\CAN\SUB \SOH(\v2*.pulsar.proto.CommandConsumerStatsResponseR\NAKconsumerStatsResponse\DC2T\n\
\\DC1reachedEndOfTopic\CAN\ESC \SOH(\v2&.pulsar.proto.CommandReachedEndOfTopicR\DC1reachedEndOfTopic\DC2-\n\
\\EOTseek\CAN\FS \SOH(\v2\EM.pulsar.proto.CommandSeekR\EOTseek\DC2Q\n\
\\DLEgetLastMessageId\CAN\GS \SOH(\v2%.pulsar.proto.CommandGetLastMessageIdR\DLEgetLastMessageId\DC2i\n\
\\CANgetLastMessageIdResponse\CAN\RS \SOH(\v2-.pulsar.proto.CommandGetLastMessageIdResponseR\CANgetLastMessageIdResponse\DC2_\n\
\\SYNactive_consumer_change\CAN\US \SOH(\v2).pulsar.proto.CommandActiveConsumerChangeR\DC4activeConsumerChange\DC2]\n\
\\DC4getTopicsOfNamespace\CAN \SOH(\v2).pulsar.proto.CommandGetTopicsOfNamespaceR\DC4getTopicsOfNamespace\DC2u\n\
\\FSgetTopicsOfNamespaceResponse\CAN! \SOH(\v21.pulsar.proto.CommandGetTopicsOfNamespaceResponseR\FSgetTopicsOfNamespaceResponse\DC2<\n\
\\tgetSchema\CAN\" \SOH(\v2\RS.pulsar.proto.CommandGetSchemaR\tgetSchema\DC2T\n\
\\DC1getSchemaResponse\CAN# \SOH(\v2&.pulsar.proto.CommandGetSchemaResponseR\DC1getSchemaResponse\DC2H\n\
\\rauthChallenge\CAN$ \SOH(\v2\".pulsar.proto.CommandAuthChallengeR\rauthChallenge\DC2E\n\
\\fauthResponse\CAN% \SOH(\v2!.pulsar.proto.CommandAuthResponseR\fauthResponse\DC2B\n\
\\vackResponse\CAN& \SOH(\v2 .pulsar.proto.CommandAckResponseR\vackResponse\DC2T\n\
\\DC1getOrCreateSchema\CAN' \SOH(\v2&.pulsar.proto.CommandGetOrCreateSchemaR\DC1getOrCreateSchema\DC2l\n\
\\EMgetOrCreateSchemaResponse\CAN( \SOH(\v2..pulsar.proto.CommandGetOrCreateSchemaResponseR\EMgetOrCreateSchemaResponse\DC23\n\
\\ACKnewTxn\CAN2 \SOH(\v2\ESC.pulsar.proto.CommandNewTxnR\ACKnewTxn\DC2K\n\
\\SOnewTxnResponse\CAN3 \SOH(\v2#.pulsar.proto.CommandNewTxnResponseR\SOnewTxnResponse\DC2T\n\
\\DC1addPartitionToTxn\CAN4 \SOH(\v2&.pulsar.proto.CommandAddPartitionToTxnR\DC1addPartitionToTxn\DC2l\n\
\\EMaddPartitionToTxnResponse\CAN5 \SOH(\v2..pulsar.proto.CommandAddPartitionToTxnResponseR\EMaddPartitionToTxnResponse\DC2]\n\
\\DC4addSubscriptionToTxn\CAN6 \SOH(\v2).pulsar.proto.CommandAddSubscriptionToTxnR\DC4addSubscriptionToTxn\DC2u\n\
\\FSaddSubscriptionToTxnResponse\CAN7 \SOH(\v21.pulsar.proto.CommandAddSubscriptionToTxnResponseR\FSaddSubscriptionToTxnResponse\DC23\n\
\\ACKendTxn\CAN8 \SOH(\v2\ESC.pulsar.proto.CommandEndTxnR\ACKendTxn\DC2K\n\
\\SOendTxnResponse\CAN9 \SOH(\v2#.pulsar.proto.CommandEndTxnResponseR\SOendTxnResponse\DC2T\n\
\\DC1endTxnOnPartition\CAN: \SOH(\v2&.pulsar.proto.CommandEndTxnOnPartitionR\DC1endTxnOnPartition\DC2l\n\
\\EMendTxnOnPartitionResponse\CAN; \SOH(\v2..pulsar.proto.CommandEndTxnOnPartitionResponseR\EMendTxnOnPartitionResponse\DC2]\n\
\\DC4endTxnOnSubscription\CAN< \SOH(\v2).pulsar.proto.CommandEndTxnOnSubscriptionR\DC4endTxnOnSubscription\DC2u\n\
\\FSendTxnOnSubscriptionResponse\CAN= \SOH(\v21.pulsar.proto.CommandEndTxnOnSubscriptionResponseR\FSendTxnOnSubscriptionResponse\"\223\b\n\
\\EOTType\DC2\v\n\
\\aCONNECT\DLE\STX\DC2\r\n\
\\tCONNECTED\DLE\ETX\DC2\r\n\
\\tSUBSCRIBE\DLE\EOT\DC2\f\n\
\\bPRODUCER\DLE\ENQ\DC2\b\n\
\\EOTSEND\DLE\ACK\DC2\DLE\n\
\\fSEND_RECEIPT\DLE\a\DC2\SO\n\
\\n\
\SEND_ERROR\DLE\b\DC2\v\n\
\\aMESSAGE\DLE\t\DC2\a\n\
\\ETXACK\DLE\n\
\\DC2\b\n\
\\EOTFLOW\DLE\v\DC2\SI\n\
\\vUNSUBSCRIBE\DLE\f\DC2\v\n\
\\aSUCCESS\DLE\r\DC2\t\n\
\\ENQERROR\DLE\SO\DC2\DC2\n\
\\SOCLOSE_PRODUCER\DLE\SI\DC2\DC2\n\
\\SOCLOSE_CONSUMER\DLE\DLE\DC2\DC4\n\
\\DLEPRODUCER_SUCCESS\DLE\DC1\DC2\b\n\
\\EOTPING\DLE\DC2\DC2\b\n\
\\EOTPONG\DLE\DC3\DC2%\n\
\!REDELIVER_UNACKNOWLEDGED_MESSAGES\DLE\DC4\DC2\CAN\n\
\\DC4PARTITIONED_METADATA\DLE\NAK\DC2!\n\
\\GSPARTITIONED_METADATA_RESPONSE\DLE\SYN\DC2\n\
\\n\
\\ACKLOOKUP\DLE\ETB\DC2\DC3\n\
\\SILOOKUP_RESPONSE\DLE\CAN\DC2\DC2\n\
\\SOCONSUMER_STATS\DLE\EM\DC2\ESC\n\
\\ETBCONSUMER_STATS_RESPONSE\DLE\SUB\DC2\CAN\n\
\\DC4REACHED_END_OF_TOPIC\DLE\ESC\DC2\b\n\
\\EOTSEEK\DLE\FS\DC2\ETB\n\
\\DC3GET_LAST_MESSAGE_ID\DLE\GS\DC2 \n\
\\FSGET_LAST_MESSAGE_ID_RESPONSE\DLE\RS\DC2\SUB\n\
\\SYNACTIVE_CONSUMER_CHANGE\DLE\US\DC2\ESC\n\
\\ETBGET_TOPICS_OF_NAMESPACE\DLE \DC2$\n\
\ GET_TOPICS_OF_NAMESPACE_RESPONSE\DLE!\DC2\SO\n\
\\n\
\GET_SCHEMA\DLE\"\DC2\ETB\n\
\\DC3GET_SCHEMA_RESPONSE\DLE#\DC2\DC2\n\
\\SOAUTH_CHALLENGE\DLE$\DC2\DC1\n\
\\rAUTH_RESPONSE\DLE%\DC2\DLE\n\
\\fACK_RESPONSE\DLE&\DC2\CAN\n\
\\DC4GET_OR_CREATE_SCHEMA\DLE'\DC2!\n\
\\GSGET_OR_CREATE_SCHEMA_RESPONSE\DLE(\DC2\v\n\
\\aNEW_TXN\DLE2\DC2\DC4\n\
\\DLENEW_TXN_RESPONSE\DLE3\DC2\CAN\n\
\\DC4ADD_PARTITION_TO_TXN\DLE4\DC2!\n\
\\GSADD_PARTITION_TO_TXN_RESPONSE\DLE5\DC2\ESC\n\
\\ETBADD_SUBSCRIPTION_TO_TXN\DLE6\DC2$\n\
\ ADD_SUBSCRIPTION_TO_TXN_RESPONSE\DLE7\DC2\v\n\
\\aEND_TXN\DLE8\DC2\DC4\n\
\\DLEEND_TXN_RESPONSE\DLE9\DC2\CAN\n\
\\DC4END_TXN_ON_PARTITION\DLE:\DC2!\n\
\\GSEND_TXN_ON_PARTITION_RESPONSE\DLE;\DC2\ESC\n\
\\ETBEND_TXN_ON_SUBSCRIPTION\DLE<\DC2$\n\
\ END_TXN_ON_SUBSCRIPTION_RESPONSE\DLE="
packedFileDescriptor :: Proxy BaseCommand -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor BaseCommand)
fieldsByTag
= let
type'__field_descriptor :: FieldDescriptor BaseCommand
type'__field_descriptor
= String
-> FieldTypeDescriptor BaseCommand'Type
-> FieldAccessor BaseCommand BaseCommand'Type
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"type"
(ScalarField BaseCommand'Type
-> FieldTypeDescriptor BaseCommand'Type
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField BaseCommand'Type
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor BaseCommand'Type)
(WireDefault BaseCommand'Type
-> Lens BaseCommand BaseCommand BaseCommand'Type BaseCommand'Type
-> FieldAccessor BaseCommand BaseCommand'Type
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault BaseCommand'Type
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
connect__field_descriptor :: FieldDescriptor BaseCommand
connect__field_descriptor
= String
-> FieldTypeDescriptor CommandConnect
-> FieldAccessor BaseCommand CommandConnect
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"connect"
(MessageOrGroup -> FieldTypeDescriptor CommandConnect
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandConnect)
(Lens
BaseCommand
BaseCommand
(Maybe CommandConnect)
(Maybe CommandConnect)
-> FieldAccessor BaseCommand CommandConnect
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'connect" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'connect")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
connected__field_descriptor :: FieldDescriptor BaseCommand
connected__field_descriptor
= String
-> FieldTypeDescriptor CommandConnected
-> FieldAccessor BaseCommand CommandConnected
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"connected"
(MessageOrGroup -> FieldTypeDescriptor CommandConnected
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandConnected)
(Lens
BaseCommand
BaseCommand
(Maybe CommandConnected)
(Maybe CommandConnected)
-> FieldAccessor BaseCommand CommandConnected
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'connected" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'connected")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
subscribe__field_descriptor :: FieldDescriptor BaseCommand
subscribe__field_descriptor
= String
-> FieldTypeDescriptor CommandSubscribe
-> FieldAccessor BaseCommand CommandSubscribe
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subscribe"
(MessageOrGroup -> FieldTypeDescriptor CommandSubscribe
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSubscribe)
(Lens
BaseCommand
BaseCommand
(Maybe CommandSubscribe)
(Maybe CommandSubscribe)
-> FieldAccessor BaseCommand CommandSubscribe
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'subscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'subscribe")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
producer__field_descriptor :: FieldDescriptor BaseCommand
producer__field_descriptor
= String
-> FieldTypeDescriptor CommandProducer
-> FieldAccessor BaseCommand CommandProducer
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer"
(MessageOrGroup -> FieldTypeDescriptor CommandProducer
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandProducer)
(Lens
BaseCommand
BaseCommand
(Maybe CommandProducer)
(Maybe CommandProducer)
-> FieldAccessor BaseCommand CommandProducer
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'producer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'producer")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
send__field_descriptor :: FieldDescriptor BaseCommand
send__field_descriptor
= String
-> FieldTypeDescriptor CommandSend
-> FieldAccessor BaseCommand CommandSend
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"send"
(MessageOrGroup -> FieldTypeDescriptor CommandSend
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSend)
(Lens
BaseCommand BaseCommand (Maybe CommandSend) (Maybe CommandSend)
-> FieldAccessor BaseCommand CommandSend
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'send" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'send")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
sendReceipt__field_descriptor :: FieldDescriptor BaseCommand
sendReceipt__field_descriptor
= String
-> FieldTypeDescriptor CommandSendReceipt
-> FieldAccessor BaseCommand CommandSendReceipt
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"send_receipt"
(MessageOrGroup -> FieldTypeDescriptor CommandSendReceipt
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSendReceipt)
(Lens
BaseCommand
BaseCommand
(Maybe CommandSendReceipt)
(Maybe CommandSendReceipt)
-> FieldAccessor BaseCommand CommandSendReceipt
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'sendReceipt" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sendReceipt")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
sendError__field_descriptor :: FieldDescriptor BaseCommand
sendError__field_descriptor
= String
-> FieldTypeDescriptor CommandSendError
-> FieldAccessor BaseCommand CommandSendError
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"send_error"
(MessageOrGroup -> FieldTypeDescriptor CommandSendError
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSendError)
(Lens
BaseCommand
BaseCommand
(Maybe CommandSendError)
(Maybe CommandSendError)
-> FieldAccessor BaseCommand CommandSendError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'sendError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sendError")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
message__field_descriptor :: FieldDescriptor BaseCommand
message__field_descriptor
= String
-> FieldTypeDescriptor CommandMessage
-> FieldAccessor BaseCommand CommandMessage
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(MessageOrGroup -> FieldTypeDescriptor CommandMessage
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandMessage)
(Lens
BaseCommand
BaseCommand
(Maybe CommandMessage)
(Maybe CommandMessage)
-> FieldAccessor BaseCommand CommandMessage
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
ack__field_descriptor :: FieldDescriptor BaseCommand
ack__field_descriptor
= String
-> FieldTypeDescriptor CommandAck
-> FieldAccessor BaseCommand CommandAck
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ack"
(MessageOrGroup -> FieldTypeDescriptor CommandAck
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAck)
(Lens BaseCommand BaseCommand (Maybe CommandAck) (Maybe CommandAck)
-> FieldAccessor BaseCommand CommandAck
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'ack" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'ack")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
flow__field_descriptor :: FieldDescriptor BaseCommand
flow__field_descriptor
= String
-> FieldTypeDescriptor CommandFlow
-> FieldAccessor BaseCommand CommandFlow
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"flow"
(MessageOrGroup -> FieldTypeDescriptor CommandFlow
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandFlow)
(Lens
BaseCommand BaseCommand (Maybe CommandFlow) (Maybe CommandFlow)
-> FieldAccessor BaseCommand CommandFlow
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'flow" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'flow")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
unsubscribe__field_descriptor :: FieldDescriptor BaseCommand
unsubscribe__field_descriptor
= String
-> FieldTypeDescriptor CommandUnsubscribe
-> FieldAccessor BaseCommand CommandUnsubscribe
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"unsubscribe"
(MessageOrGroup -> FieldTypeDescriptor CommandUnsubscribe
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandUnsubscribe)
(Lens
BaseCommand
BaseCommand
(Maybe CommandUnsubscribe)
(Maybe CommandUnsubscribe)
-> FieldAccessor BaseCommand CommandUnsubscribe
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'unsubscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'unsubscribe")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
success__field_descriptor :: FieldDescriptor BaseCommand
success__field_descriptor
= String
-> FieldTypeDescriptor CommandSuccess
-> FieldAccessor BaseCommand CommandSuccess
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"success"
(MessageOrGroup -> FieldTypeDescriptor CommandSuccess
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSuccess)
(Lens
BaseCommand
BaseCommand
(Maybe CommandSuccess)
(Maybe CommandSuccess)
-> FieldAccessor BaseCommand CommandSuccess
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'success" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'success")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
error__field_descriptor :: FieldDescriptor BaseCommand
error__field_descriptor
= String
-> FieldTypeDescriptor CommandError
-> FieldAccessor BaseCommand CommandError
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(MessageOrGroup -> FieldTypeDescriptor CommandError
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandError)
(Lens
BaseCommand BaseCommand (Maybe CommandError) (Maybe CommandError)
-> FieldAccessor BaseCommand CommandError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
closeProducer__field_descriptor :: FieldDescriptor BaseCommand
closeProducer__field_descriptor
= String
-> FieldTypeDescriptor CommandCloseProducer
-> FieldAccessor BaseCommand CommandCloseProducer
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"close_producer"
(MessageOrGroup -> FieldTypeDescriptor CommandCloseProducer
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandCloseProducer)
(Lens
BaseCommand
BaseCommand
(Maybe CommandCloseProducer)
(Maybe CommandCloseProducer)
-> FieldAccessor BaseCommand CommandCloseProducer
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'closeProducer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'closeProducer")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
closeConsumer__field_descriptor :: FieldDescriptor BaseCommand
closeConsumer__field_descriptor
= String
-> FieldTypeDescriptor CommandCloseConsumer
-> FieldAccessor BaseCommand CommandCloseConsumer
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"close_consumer"
(MessageOrGroup -> FieldTypeDescriptor CommandCloseConsumer
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandCloseConsumer)
(Lens
BaseCommand
BaseCommand
(Maybe CommandCloseConsumer)
(Maybe CommandCloseConsumer)
-> FieldAccessor BaseCommand CommandCloseConsumer
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'closeConsumer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'closeConsumer")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
producerSuccess__field_descriptor :: FieldDescriptor BaseCommand
producerSuccess__field_descriptor
= String
-> FieldTypeDescriptor CommandProducerSuccess
-> FieldAccessor BaseCommand CommandProducerSuccess
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_success"
(MessageOrGroup -> FieldTypeDescriptor CommandProducerSuccess
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandProducerSuccess)
(Lens
BaseCommand
BaseCommand
(Maybe CommandProducerSuccess)
(Maybe CommandProducerSuccess)
-> FieldAccessor BaseCommand CommandProducerSuccess
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'producerSuccess" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'producerSuccess")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
ping__field_descriptor :: FieldDescriptor BaseCommand
ping__field_descriptor
= String
-> FieldTypeDescriptor CommandPing
-> FieldAccessor BaseCommand CommandPing
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ping"
(MessageOrGroup -> FieldTypeDescriptor CommandPing
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandPing)
(Lens
BaseCommand BaseCommand (Maybe CommandPing) (Maybe CommandPing)
-> FieldAccessor BaseCommand CommandPing
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'ping" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'ping")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
pong__field_descriptor :: FieldDescriptor BaseCommand
pong__field_descriptor
= String
-> FieldTypeDescriptor CommandPong
-> FieldAccessor BaseCommand CommandPong
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"pong"
(MessageOrGroup -> FieldTypeDescriptor CommandPong
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandPong)
(Lens
BaseCommand BaseCommand (Maybe CommandPong) (Maybe CommandPong)
-> FieldAccessor BaseCommand CommandPong
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'pong" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'pong")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
redeliverUnacknowledgedMessages__field_descriptor :: FieldDescriptor BaseCommand
redeliverUnacknowledgedMessages__field_descriptor
= String
-> FieldTypeDescriptor CommandRedeliverUnacknowledgedMessages
-> FieldAccessor BaseCommand CommandRedeliverUnacknowledgedMessages
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"redeliverUnacknowledgedMessages"
(MessageOrGroup
-> FieldTypeDescriptor CommandRedeliverUnacknowledgedMessages
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandRedeliverUnacknowledgedMessages)
(Lens
BaseCommand
BaseCommand
(Maybe CommandRedeliverUnacknowledgedMessages)
(Maybe CommandRedeliverUnacknowledgedMessages)
-> FieldAccessor BaseCommand CommandRedeliverUnacknowledgedMessages
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'redeliverUnacknowledgedMessages" a,
Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'redeliverUnacknowledgedMessages")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
partitionMetadata__field_descriptor :: FieldDescriptor BaseCommand
partitionMetadata__field_descriptor
= String
-> FieldTypeDescriptor CommandPartitionedTopicMetadata
-> FieldAccessor BaseCommand CommandPartitionedTopicMetadata
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partitionMetadata"
(MessageOrGroup
-> FieldTypeDescriptor CommandPartitionedTopicMetadata
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandPartitionedTopicMetadata)
(Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadata)
(Maybe CommandPartitionedTopicMetadata)
-> FieldAccessor BaseCommand CommandPartitionedTopicMetadata
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionMetadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionMetadata")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
partitionMetadataResponse__field_descriptor :: FieldDescriptor BaseCommand
partitionMetadataResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandPartitionedTopicMetadataResponse
-> FieldAccessor
BaseCommand CommandPartitionedTopicMetadataResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partitionMetadataResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandPartitionedTopicMetadataResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandPartitionedTopicMetadataResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadataResponse)
(Maybe CommandPartitionedTopicMetadataResponse)
-> FieldAccessor
BaseCommand CommandPartitionedTopicMetadataResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionMetadataResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionMetadataResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
lookupTopic__field_descriptor :: FieldDescriptor BaseCommand
lookupTopic__field_descriptor
= String
-> FieldTypeDescriptor CommandLookupTopic
-> FieldAccessor BaseCommand CommandLookupTopic
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"lookupTopic"
(MessageOrGroup -> FieldTypeDescriptor CommandLookupTopic
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandLookupTopic)
(Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopic)
(Maybe CommandLookupTopic)
-> FieldAccessor BaseCommand CommandLookupTopic
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'lookupTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'lookupTopic")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
lookupTopicResponse__field_descriptor :: FieldDescriptor BaseCommand
lookupTopicResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandLookupTopicResponse
-> FieldAccessor BaseCommand CommandLookupTopicResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"lookupTopicResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandLookupTopicResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandLookupTopicResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandLookupTopicResponse)
(Maybe CommandLookupTopicResponse)
-> FieldAccessor BaseCommand CommandLookupTopicResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'lookupTopicResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'lookupTopicResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
consumerStats__field_descriptor :: FieldDescriptor BaseCommand
consumerStats__field_descriptor
= String
-> FieldTypeDescriptor CommandConsumerStats
-> FieldAccessor BaseCommand CommandConsumerStats
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumerStats"
(MessageOrGroup -> FieldTypeDescriptor CommandConsumerStats
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandConsumerStats)
(Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStats)
(Maybe CommandConsumerStats)
-> FieldAccessor BaseCommand CommandConsumerStats
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'consumerStats" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerStats")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
consumerStatsResponse__field_descriptor :: FieldDescriptor BaseCommand
consumerStatsResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandConsumerStatsResponse
-> FieldAccessor BaseCommand CommandConsumerStatsResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumerStatsResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandConsumerStatsResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandConsumerStatsResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandConsumerStatsResponse)
(Maybe CommandConsumerStatsResponse)
-> FieldAccessor BaseCommand CommandConsumerStatsResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'consumerStatsResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerStatsResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
reachedEndOfTopic__field_descriptor :: FieldDescriptor BaseCommand
reachedEndOfTopic__field_descriptor
= String
-> FieldTypeDescriptor CommandReachedEndOfTopic
-> FieldAccessor BaseCommand CommandReachedEndOfTopic
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"reachedEndOfTopic"
(MessageOrGroup -> FieldTypeDescriptor CommandReachedEndOfTopic
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandReachedEndOfTopic)
(Lens
BaseCommand
BaseCommand
(Maybe CommandReachedEndOfTopic)
(Maybe CommandReachedEndOfTopic)
-> FieldAccessor BaseCommand CommandReachedEndOfTopic
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'reachedEndOfTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'reachedEndOfTopic")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
seek__field_descriptor :: FieldDescriptor BaseCommand
seek__field_descriptor
= String
-> FieldTypeDescriptor CommandSeek
-> FieldAccessor BaseCommand CommandSeek
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"seek"
(MessageOrGroup -> FieldTypeDescriptor CommandSeek
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandSeek)
(Lens
BaseCommand BaseCommand (Maybe CommandSeek) (Maybe CommandSeek)
-> FieldAccessor BaseCommand CommandSeek
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'seek" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'seek")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getLastMessageId__field_descriptor :: FieldDescriptor BaseCommand
getLastMessageId__field_descriptor
= String
-> FieldTypeDescriptor CommandGetLastMessageId
-> FieldAccessor BaseCommand CommandGetLastMessageId
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getLastMessageId"
(MessageOrGroup -> FieldTypeDescriptor CommandGetLastMessageId
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetLastMessageId)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageId)
(Maybe CommandGetLastMessageId)
-> FieldAccessor BaseCommand CommandGetLastMessageId
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getLastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getLastMessageId")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getLastMessageIdResponse__field_descriptor :: FieldDescriptor BaseCommand
getLastMessageIdResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandGetLastMessageIdResponse
-> FieldAccessor BaseCommand CommandGetLastMessageIdResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getLastMessageIdResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandGetLastMessageIdResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetLastMessageIdResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageIdResponse)
(Maybe CommandGetLastMessageIdResponse)
-> FieldAccessor BaseCommand CommandGetLastMessageIdResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getLastMessageIdResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getLastMessageIdResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
activeConsumerChange__field_descriptor :: FieldDescriptor BaseCommand
activeConsumerChange__field_descriptor
= String
-> FieldTypeDescriptor CommandActiveConsumerChange
-> FieldAccessor BaseCommand CommandActiveConsumerChange
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"active_consumer_change"
(MessageOrGroup -> FieldTypeDescriptor CommandActiveConsumerChange
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandActiveConsumerChange)
(Lens
BaseCommand
BaseCommand
(Maybe CommandActiveConsumerChange)
(Maybe CommandActiveConsumerChange)
-> FieldAccessor BaseCommand CommandActiveConsumerChange
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'activeConsumerChange" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'activeConsumerChange")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getTopicsOfNamespace__field_descriptor :: FieldDescriptor BaseCommand
getTopicsOfNamespace__field_descriptor
= String
-> FieldTypeDescriptor CommandGetTopicsOfNamespace
-> FieldAccessor BaseCommand CommandGetTopicsOfNamespace
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getTopicsOfNamespace"
(MessageOrGroup -> FieldTypeDescriptor CommandGetTopicsOfNamespace
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetTopicsOfNamespace)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespace)
(Maybe CommandGetTopicsOfNamespace)
-> FieldAccessor BaseCommand CommandGetTopicsOfNamespace
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getTopicsOfNamespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getTopicsOfNamespace")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getTopicsOfNamespaceResponse__field_descriptor :: FieldDescriptor BaseCommand
getTopicsOfNamespaceResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandGetTopicsOfNamespaceResponse
-> FieldAccessor BaseCommand CommandGetTopicsOfNamespaceResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getTopicsOfNamespaceResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandGetTopicsOfNamespaceResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetTopicsOfNamespaceResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespaceResponse)
(Maybe CommandGetTopicsOfNamespaceResponse)
-> FieldAccessor BaseCommand CommandGetTopicsOfNamespaceResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getTopicsOfNamespaceResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getTopicsOfNamespaceResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getSchema__field_descriptor :: FieldDescriptor BaseCommand
getSchema__field_descriptor
= String
-> FieldTypeDescriptor CommandGetSchema
-> FieldAccessor BaseCommand CommandGetSchema
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getSchema"
(MessageOrGroup -> FieldTypeDescriptor CommandGetSchema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetSchema)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchema)
(Maybe CommandGetSchema)
-> FieldAccessor BaseCommand CommandGetSchema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getSchema")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getSchemaResponse__field_descriptor :: FieldDescriptor BaseCommand
getSchemaResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandGetSchemaResponse
-> FieldAccessor BaseCommand CommandGetSchemaResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getSchemaResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandGetSchemaResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetSchemaResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetSchemaResponse)
(Maybe CommandGetSchemaResponse)
-> FieldAccessor BaseCommand CommandGetSchemaResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getSchemaResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
authChallenge__field_descriptor :: FieldDescriptor BaseCommand
authChallenge__field_descriptor
= String
-> FieldTypeDescriptor CommandAuthChallenge
-> FieldAccessor BaseCommand CommandAuthChallenge
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"authChallenge"
(MessageOrGroup -> FieldTypeDescriptor CommandAuthChallenge
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAuthChallenge)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAuthChallenge)
(Maybe CommandAuthChallenge)
-> FieldAccessor BaseCommand CommandAuthChallenge
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authChallenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authChallenge")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
authResponse__field_descriptor :: FieldDescriptor BaseCommand
authResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandAuthResponse
-> FieldAccessor BaseCommand CommandAuthResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"authResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandAuthResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAuthResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAuthResponse)
(Maybe CommandAuthResponse)
-> FieldAccessor BaseCommand CommandAuthResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
ackResponse__field_descriptor :: FieldDescriptor BaseCommand
ackResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandAckResponse
-> FieldAccessor BaseCommand CommandAckResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ackResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandAckResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAckResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAckResponse)
(Maybe CommandAckResponse)
-> FieldAccessor BaseCommand CommandAckResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'ackResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'ackResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getOrCreateSchema__field_descriptor :: FieldDescriptor BaseCommand
getOrCreateSchema__field_descriptor
= String
-> FieldTypeDescriptor CommandGetOrCreateSchema
-> FieldAccessor BaseCommand CommandGetOrCreateSchema
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getOrCreateSchema"
(MessageOrGroup -> FieldTypeDescriptor CommandGetOrCreateSchema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetOrCreateSchema)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchema)
(Maybe CommandGetOrCreateSchema)
-> FieldAccessor BaseCommand CommandGetOrCreateSchema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getOrCreateSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getOrCreateSchema")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
getOrCreateSchemaResponse__field_descriptor :: FieldDescriptor BaseCommand
getOrCreateSchemaResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandGetOrCreateSchemaResponse
-> FieldAccessor BaseCommand CommandGetOrCreateSchemaResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"getOrCreateSchemaResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandGetOrCreateSchemaResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandGetOrCreateSchemaResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchemaResponse)
(Maybe CommandGetOrCreateSchemaResponse)
-> FieldAccessor BaseCommand CommandGetOrCreateSchemaResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'getOrCreateSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'getOrCreateSchemaResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
newTxn__field_descriptor :: FieldDescriptor BaseCommand
newTxn__field_descriptor
= String
-> FieldTypeDescriptor CommandNewTxn
-> FieldAccessor BaseCommand CommandNewTxn
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"newTxn"
(MessageOrGroup -> FieldTypeDescriptor CommandNewTxn
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandNewTxn)
(Lens
BaseCommand BaseCommand (Maybe CommandNewTxn) (Maybe CommandNewTxn)
-> FieldAccessor BaseCommand CommandNewTxn
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'newTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'newTxn")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
newTxnResponse__field_descriptor :: FieldDescriptor BaseCommand
newTxnResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandNewTxnResponse
-> FieldAccessor BaseCommand CommandNewTxnResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"newTxnResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandNewTxnResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandNewTxnResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandNewTxnResponse)
(Maybe CommandNewTxnResponse)
-> FieldAccessor BaseCommand CommandNewTxnResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'newTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'newTxnResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
addPartitionToTxn__field_descriptor :: FieldDescriptor BaseCommand
addPartitionToTxn__field_descriptor
= String
-> FieldTypeDescriptor CommandAddPartitionToTxn
-> FieldAccessor BaseCommand CommandAddPartitionToTxn
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"addPartitionToTxn"
(MessageOrGroup -> FieldTypeDescriptor CommandAddPartitionToTxn
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAddPartitionToTxn)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxn)
(Maybe CommandAddPartitionToTxn)
-> FieldAccessor BaseCommand CommandAddPartitionToTxn
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'addPartitionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'addPartitionToTxn")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
addPartitionToTxnResponse__field_descriptor :: FieldDescriptor BaseCommand
addPartitionToTxnResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandAddPartitionToTxnResponse
-> FieldAccessor BaseCommand CommandAddPartitionToTxnResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"addPartitionToTxnResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandAddPartitionToTxnResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAddPartitionToTxnResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxnResponse)
(Maybe CommandAddPartitionToTxnResponse)
-> FieldAccessor BaseCommand CommandAddPartitionToTxnResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'addPartitionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'addPartitionToTxnResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
addSubscriptionToTxn__field_descriptor :: FieldDescriptor BaseCommand
addSubscriptionToTxn__field_descriptor
= String
-> FieldTypeDescriptor CommandAddSubscriptionToTxn
-> FieldAccessor BaseCommand CommandAddSubscriptionToTxn
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"addSubscriptionToTxn"
(MessageOrGroup -> FieldTypeDescriptor CommandAddSubscriptionToTxn
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAddSubscriptionToTxn)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxn)
(Maybe CommandAddSubscriptionToTxn)
-> FieldAccessor BaseCommand CommandAddSubscriptionToTxn
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'addSubscriptionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'addSubscriptionToTxn")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
addSubscriptionToTxnResponse__field_descriptor :: FieldDescriptor BaseCommand
addSubscriptionToTxnResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandAddSubscriptionToTxnResponse
-> FieldAccessor BaseCommand CommandAddSubscriptionToTxnResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"addSubscriptionToTxnResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandAddSubscriptionToTxnResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandAddSubscriptionToTxnResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxnResponse)
(Maybe CommandAddSubscriptionToTxnResponse)
-> FieldAccessor BaseCommand CommandAddSubscriptionToTxnResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'addSubscriptionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'addSubscriptionToTxnResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxn__field_descriptor :: FieldDescriptor BaseCommand
endTxn__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxn
-> FieldAccessor BaseCommand CommandEndTxn
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxn"
(MessageOrGroup -> FieldTypeDescriptor CommandEndTxn
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxn)
(Lens
BaseCommand BaseCommand (Maybe CommandEndTxn) (Maybe CommandEndTxn)
-> FieldAccessor BaseCommand CommandEndTxn
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'endTxn")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxnResponse__field_descriptor :: FieldDescriptor BaseCommand
endTxnResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxnResponse
-> FieldAccessor BaseCommand CommandEndTxnResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxnResponse"
(MessageOrGroup -> FieldTypeDescriptor CommandEndTxnResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxnResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnResponse)
(Maybe CommandEndTxnResponse)
-> FieldAccessor BaseCommand CommandEndTxnResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'endTxnResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxnOnPartition__field_descriptor :: FieldDescriptor BaseCommand
endTxnOnPartition__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxnOnPartition
-> FieldAccessor BaseCommand CommandEndTxnOnPartition
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxnOnPartition"
(MessageOrGroup -> FieldTypeDescriptor CommandEndTxnOnPartition
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxnOnPartition)
(Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartition)
(Maybe CommandEndTxnOnPartition)
-> FieldAccessor BaseCommand CommandEndTxnOnPartition
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnPartition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'endTxnOnPartition")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxnOnPartitionResponse__field_descriptor :: FieldDescriptor BaseCommand
endTxnOnPartitionResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxnOnPartitionResponse
-> FieldAccessor BaseCommand CommandEndTxnOnPartitionResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxnOnPartitionResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandEndTxnOnPartitionResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxnOnPartitionResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartitionResponse)
(Maybe CommandEndTxnOnPartitionResponse)
-> FieldAccessor BaseCommand CommandEndTxnOnPartitionResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnPartitionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'endTxnOnPartitionResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxnOnSubscription__field_descriptor :: FieldDescriptor BaseCommand
endTxnOnSubscription__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxnOnSubscription
-> FieldAccessor BaseCommand CommandEndTxnOnSubscription
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxnOnSubscription"
(MessageOrGroup -> FieldTypeDescriptor CommandEndTxnOnSubscription
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxnOnSubscription)
(Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscription)
(Maybe CommandEndTxnOnSubscription)
-> FieldAccessor BaseCommand CommandEndTxnOnSubscription
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnSubscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'endTxnOnSubscription")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
endTxnOnSubscriptionResponse__field_descriptor :: FieldDescriptor BaseCommand
endTxnOnSubscriptionResponse__field_descriptor
= String
-> FieldTypeDescriptor CommandEndTxnOnSubscriptionResponse
-> FieldAccessor BaseCommand CommandEndTxnOnSubscriptionResponse
-> FieldDescriptor BaseCommand
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"endTxnOnSubscriptionResponse"
(MessageOrGroup
-> FieldTypeDescriptor CommandEndTxnOnSubscriptionResponse
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor CommandEndTxnOnSubscriptionResponse)
(Lens
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscriptionResponse)
(Maybe CommandEndTxnOnSubscriptionResponse)
-> FieldAccessor BaseCommand CommandEndTxnOnSubscriptionResponse
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnSubscriptionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnOnSubscriptionResponse")) ::
Data.ProtoLens.FieldDescriptor BaseCommand
in
[(Tag, FieldDescriptor BaseCommand)]
-> Map Tag (FieldDescriptor BaseCommand)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor BaseCommand
type'__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor BaseCommand
connect__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor BaseCommand
connected__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor BaseCommand
subscribe__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor BaseCommand
producer__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor BaseCommand
send__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor BaseCommand
sendReceipt__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor BaseCommand
sendError__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor BaseCommand
message__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 10, FieldDescriptor BaseCommand
ack__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 11, FieldDescriptor BaseCommand
flow__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 12, FieldDescriptor BaseCommand
unsubscribe__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 13, FieldDescriptor BaseCommand
success__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 14, FieldDescriptor BaseCommand
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 15, FieldDescriptor BaseCommand
closeProducer__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 16, FieldDescriptor BaseCommand
closeConsumer__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 17, FieldDescriptor BaseCommand
producerSuccess__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 18, FieldDescriptor BaseCommand
ping__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 19, FieldDescriptor BaseCommand
pong__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 20,
FieldDescriptor BaseCommand
redeliverUnacknowledgedMessages__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 21, FieldDescriptor BaseCommand
partitionMetadata__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 22,
FieldDescriptor BaseCommand
partitionMetadataResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 23, FieldDescriptor BaseCommand
lookupTopic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 24, FieldDescriptor BaseCommand
lookupTopicResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 25, FieldDescriptor BaseCommand
consumerStats__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 26, FieldDescriptor BaseCommand
consumerStatsResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 27, FieldDescriptor BaseCommand
reachedEndOfTopic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 28, FieldDescriptor BaseCommand
seek__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 29, FieldDescriptor BaseCommand
getLastMessageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 30,
FieldDescriptor BaseCommand
getLastMessageIdResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 31, FieldDescriptor BaseCommand
activeConsumerChange__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 32, FieldDescriptor BaseCommand
getTopicsOfNamespace__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 33,
FieldDescriptor BaseCommand
getTopicsOfNamespaceResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 34, FieldDescriptor BaseCommand
getSchema__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 35, FieldDescriptor BaseCommand
getSchemaResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 36, FieldDescriptor BaseCommand
authChallenge__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 37, FieldDescriptor BaseCommand
authResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 38, FieldDescriptor BaseCommand
ackResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 39, FieldDescriptor BaseCommand
getOrCreateSchema__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 40,
FieldDescriptor BaseCommand
getOrCreateSchemaResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 50, FieldDescriptor BaseCommand
newTxn__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 51, FieldDescriptor BaseCommand
newTxnResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 52, FieldDescriptor BaseCommand
addPartitionToTxn__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 53,
FieldDescriptor BaseCommand
addPartitionToTxnResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 54, FieldDescriptor BaseCommand
addSubscriptionToTxn__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 55,
FieldDescriptor BaseCommand
addSubscriptionToTxnResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 56, FieldDescriptor BaseCommand
endTxn__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 57, FieldDescriptor BaseCommand
endTxnResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 58, FieldDescriptor BaseCommand
endTxnOnPartition__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 59,
FieldDescriptor BaseCommand
endTxnOnPartitionResponse__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 60, FieldDescriptor BaseCommand
endTxnOnSubscription__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 61,
FieldDescriptor BaseCommand
endTxnOnSubscriptionResponse__field_descriptor)]
unknownFields :: LensLike' f BaseCommand FieldSet
unknownFields
= (BaseCommand -> FieldSet)
-> (BaseCommand -> FieldSet -> BaseCommand)
-> Lens' BaseCommand FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BaseCommand -> FieldSet
_BaseCommand'_unknownFields
(\ x__ :: BaseCommand
x__ y__ :: FieldSet
y__ -> BaseCommand
x__ {_BaseCommand'_unknownFields :: FieldSet
_BaseCommand'_unknownFields = FieldSet
y__})
defMessage :: BaseCommand
defMessage
= $WBaseCommand'_constructor :: BaseCommand'Type
-> Maybe CommandConnect
-> Maybe CommandConnected
-> Maybe CommandSubscribe
-> Maybe CommandProducer
-> Maybe CommandSend
-> Maybe CommandSendReceipt
-> Maybe CommandSendError
-> Maybe CommandMessage
-> Maybe CommandAck
-> Maybe CommandFlow
-> Maybe CommandUnsubscribe
-> Maybe CommandSuccess
-> Maybe CommandError
-> Maybe CommandCloseProducer
-> Maybe CommandCloseConsumer
-> Maybe CommandProducerSuccess
-> Maybe CommandPing
-> Maybe CommandPong
-> Maybe CommandRedeliverUnacknowledgedMessages
-> Maybe CommandPartitionedTopicMetadata
-> Maybe CommandPartitionedTopicMetadataResponse
-> Maybe CommandLookupTopic
-> Maybe CommandLookupTopicResponse
-> Maybe CommandConsumerStats
-> Maybe CommandConsumerStatsResponse
-> Maybe CommandReachedEndOfTopic
-> Maybe CommandSeek
-> Maybe CommandGetLastMessageId
-> Maybe CommandGetLastMessageIdResponse
-> Maybe CommandActiveConsumerChange
-> Maybe CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespaceResponse
-> Maybe CommandGetSchema
-> Maybe CommandGetSchemaResponse
-> Maybe CommandAuthChallenge
-> Maybe CommandAuthResponse
-> Maybe CommandAckResponse
-> Maybe CommandGetOrCreateSchema
-> Maybe CommandGetOrCreateSchemaResponse
-> Maybe CommandNewTxn
-> Maybe CommandNewTxnResponse
-> Maybe CommandAddPartitionToTxn
-> Maybe CommandAddPartitionToTxnResponse
-> Maybe CommandAddSubscriptionToTxn
-> Maybe CommandAddSubscriptionToTxnResponse
-> Maybe CommandEndTxn
-> Maybe CommandEndTxnResponse
-> Maybe CommandEndTxnOnPartition
-> Maybe CommandEndTxnOnPartitionResponse
-> Maybe CommandEndTxnOnSubscription
-> Maybe CommandEndTxnOnSubscriptionResponse
-> FieldSet
-> BaseCommand
BaseCommand'_constructor
{_BaseCommand'type' :: BaseCommand'Type
_BaseCommand'type' = BaseCommand'Type
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_BaseCommand'connect :: Maybe CommandConnect
_BaseCommand'connect = Maybe CommandConnect
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'connected :: Maybe CommandConnected
_BaseCommand'connected = Maybe CommandConnected
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'subscribe :: Maybe CommandSubscribe
_BaseCommand'subscribe = Maybe CommandSubscribe
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'producer :: Maybe CommandProducer
_BaseCommand'producer = Maybe CommandProducer
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'send :: Maybe CommandSend
_BaseCommand'send = Maybe CommandSend
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'sendReceipt :: Maybe CommandSendReceipt
_BaseCommand'sendReceipt = Maybe CommandSendReceipt
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'sendError :: Maybe CommandSendError
_BaseCommand'sendError = Maybe CommandSendError
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'message :: Maybe CommandMessage
_BaseCommand'message = Maybe CommandMessage
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'ack :: Maybe CommandAck
_BaseCommand'ack = Maybe CommandAck
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'flow :: Maybe CommandFlow
_BaseCommand'flow = Maybe CommandFlow
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'unsubscribe :: Maybe CommandUnsubscribe
_BaseCommand'unsubscribe = Maybe CommandUnsubscribe
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'success :: Maybe CommandSuccess
_BaseCommand'success = Maybe CommandSuccess
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'error :: Maybe CommandError
_BaseCommand'error = Maybe CommandError
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'closeProducer :: Maybe CommandCloseProducer
_BaseCommand'closeProducer = Maybe CommandCloseProducer
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'closeConsumer :: Maybe CommandCloseConsumer
_BaseCommand'closeConsumer = Maybe CommandCloseConsumer
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'producerSuccess :: Maybe CommandProducerSuccess
_BaseCommand'producerSuccess = Maybe CommandProducerSuccess
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'ping :: Maybe CommandPing
_BaseCommand'ping = Maybe CommandPing
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'pong :: Maybe CommandPong
_BaseCommand'pong = Maybe CommandPong
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'redeliverUnacknowledgedMessages :: Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages = Maybe CommandRedeliverUnacknowledgedMessages
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'partitionMetadata :: Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata = Maybe CommandPartitionedTopicMetadata
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'partitionMetadataResponse :: Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse = Maybe CommandPartitionedTopicMetadataResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'lookupTopic :: Maybe CommandLookupTopic
_BaseCommand'lookupTopic = Maybe CommandLookupTopic
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'lookupTopicResponse :: Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse = Maybe CommandLookupTopicResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'consumerStats :: Maybe CommandConsumerStats
_BaseCommand'consumerStats = Maybe CommandConsumerStats
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'consumerStatsResponse :: Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse = Maybe CommandConsumerStatsResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'reachedEndOfTopic :: Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic = Maybe CommandReachedEndOfTopic
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'seek :: Maybe CommandSeek
_BaseCommand'seek = Maybe CommandSeek
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getLastMessageId :: Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId = Maybe CommandGetLastMessageId
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getLastMessageIdResponse :: Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse = Maybe CommandGetLastMessageIdResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'activeConsumerChange :: Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange = Maybe CommandActiveConsumerChange
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getTopicsOfNamespace :: Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace = Maybe CommandGetTopicsOfNamespace
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getTopicsOfNamespaceResponse :: Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse = Maybe CommandGetTopicsOfNamespaceResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getSchema :: Maybe CommandGetSchema
_BaseCommand'getSchema = Maybe CommandGetSchema
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getSchemaResponse :: Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse = Maybe CommandGetSchemaResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'authChallenge :: Maybe CommandAuthChallenge
_BaseCommand'authChallenge = Maybe CommandAuthChallenge
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'authResponse :: Maybe CommandAuthResponse
_BaseCommand'authResponse = Maybe CommandAuthResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'ackResponse :: Maybe CommandAckResponse
_BaseCommand'ackResponse = Maybe CommandAckResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getOrCreateSchema :: Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema = Maybe CommandGetOrCreateSchema
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'getOrCreateSchemaResponse :: Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse = Maybe CommandGetOrCreateSchemaResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'newTxn :: Maybe CommandNewTxn
_BaseCommand'newTxn = Maybe CommandNewTxn
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'newTxnResponse :: Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse = Maybe CommandNewTxnResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'addPartitionToTxn :: Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn = Maybe CommandAddPartitionToTxn
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'addPartitionToTxnResponse :: Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse = Maybe CommandAddPartitionToTxnResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'addSubscriptionToTxn :: Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn = Maybe CommandAddSubscriptionToTxn
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'addSubscriptionToTxnResponse :: Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse = Maybe CommandAddSubscriptionToTxnResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxn :: Maybe CommandEndTxn
_BaseCommand'endTxn = Maybe CommandEndTxn
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxnResponse :: Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse = Maybe CommandEndTxnResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxnOnPartition :: Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition = Maybe CommandEndTxnOnPartition
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxnOnPartitionResponse :: Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse = Maybe CommandEndTxnOnPartitionResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxnOnSubscription :: Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription = Maybe CommandEndTxnOnSubscription
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'endTxnOnSubscriptionResponse :: Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse = Maybe CommandEndTxnOnSubscriptionResponse
forall a. Maybe a
Prelude.Nothing,
_BaseCommand'_unknownFields :: FieldSet
_BaseCommand'_unknownFields = []}
parseMessage :: Parser BaseCommand
parseMessage
= let
loop ::
BaseCommand
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser BaseCommand
loop :: BaseCommand -> Bool -> Parser BaseCommand
loop x :: BaseCommand
x required'type' :: Bool
required'type'
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing = (if Bool
required'type' then (:) "type" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
BaseCommand -> Parser BaseCommand
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter BaseCommand BaseCommand FieldSet FieldSet
-> (FieldSet -> FieldSet) -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter BaseCommand BaseCommand FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) BaseCommand
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do BaseCommand'Type
y <- Parser BaseCommand'Type -> String -> Parser BaseCommand'Type
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> BaseCommand'Type) -> Parser Int -> Parser BaseCommand'Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> BaseCommand'Type
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"type"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand BaseCommand'Type BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'") BaseCommand'Type
y BaseCommand
x)
Bool
Prelude.False
18
-> do CommandConnect
y <- Parser CommandConnect -> String -> Parser CommandConnect
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandConnect -> Parser CommandConnect
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandConnect
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"connect"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandConnect CommandConnect
-> CommandConnect -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "connect" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"connect") CommandConnect
y BaseCommand
x)
Bool
required'type'
26
-> do CommandConnected
y <- Parser CommandConnected -> String -> Parser CommandConnected
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandConnected -> Parser CommandConnected
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandConnected
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"connected"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandConnected CommandConnected
-> CommandConnected -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "connected" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"connected") CommandConnected
y BaseCommand
x)
Bool
required'type'
34
-> do CommandSubscribe
y <- Parser CommandSubscribe -> String -> Parser CommandSubscribe
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSubscribe -> Parser CommandSubscribe
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSubscribe
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"subscribe"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandSubscribe CommandSubscribe
-> CommandSubscribe -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "subscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscribe") CommandSubscribe
y BaseCommand
x)
Bool
required'type'
42
-> do CommandProducer
y <- Parser CommandProducer -> String -> Parser CommandProducer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandProducer -> Parser CommandProducer
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandProducer
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"producer"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandProducer CommandProducer
-> CommandProducer -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producer") CommandProducer
y BaseCommand
x)
Bool
required'type'
50
-> do CommandSend
y <- Parser CommandSend -> String -> Parser CommandSend
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSend -> Parser CommandSend
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSend
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"send"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandSend CommandSend
-> CommandSend -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "send" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"send") CommandSend
y BaseCommand
x)
Bool
required'type'
58
-> do CommandSendReceipt
y <- Parser CommandSendReceipt -> String -> Parser CommandSendReceipt
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSendReceipt -> Parser CommandSendReceipt
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSendReceipt
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"send_receipt"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandSendReceipt CommandSendReceipt
-> CommandSendReceipt -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sendReceipt" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sendReceipt") CommandSendReceipt
y BaseCommand
x)
Bool
required'type'
66
-> do CommandSendError
y <- Parser CommandSendError -> String -> Parser CommandSendError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSendError -> Parser CommandSendError
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSendError
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"send_error"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandSendError CommandSendError
-> CommandSendError -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sendError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sendError") CommandSendError
y BaseCommand
x)
Bool
required'type'
74
-> do CommandMessage
y <- Parser CommandMessage -> String -> Parser CommandMessage
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandMessage -> Parser CommandMessage
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandMessage
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandMessage CommandMessage
-> CommandMessage -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") CommandMessage
y BaseCommand
x)
Bool
required'type'
82
-> do CommandAck
y <- Parser CommandAck -> String -> Parser CommandAck
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandAck -> Parser CommandAck
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAck
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"ack"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandAck CommandAck
-> CommandAck -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "ack" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ack") CommandAck
y BaseCommand
x)
Bool
required'type'
90
-> do CommandFlow
y <- Parser CommandFlow -> String -> Parser CommandFlow
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandFlow -> Parser CommandFlow
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandFlow
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"flow"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandFlow CommandFlow
-> CommandFlow -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "flow" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"flow") CommandFlow
y BaseCommand
x)
Bool
required'type'
98
-> do CommandUnsubscribe
y <- Parser CommandUnsubscribe -> String -> Parser CommandUnsubscribe
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandUnsubscribe -> Parser CommandUnsubscribe
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandUnsubscribe
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"unsubscribe"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandUnsubscribe CommandUnsubscribe
-> CommandUnsubscribe -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "unsubscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"unsubscribe") CommandUnsubscribe
y BaseCommand
x)
Bool
required'type'
106
-> do CommandSuccess
y <- Parser CommandSuccess -> String -> Parser CommandSuccess
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSuccess -> Parser CommandSuccess
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSuccess
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"success"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandSuccess CommandSuccess
-> CommandSuccess -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "success" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"success") CommandSuccess
y BaseCommand
x)
Bool
required'type'
114
-> do CommandError
y <- Parser CommandError -> String -> Parser CommandError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandError -> Parser CommandError
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandError
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"error"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandError CommandError
-> CommandError -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") CommandError
y BaseCommand
x)
Bool
required'type'
122
-> do CommandCloseProducer
y <- Parser CommandCloseProducer
-> String -> Parser CommandCloseProducer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandCloseProducer -> Parser CommandCloseProducer
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandCloseProducer
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"close_producer"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandCloseProducer CommandCloseProducer
-> CommandCloseProducer -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "closeProducer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"closeProducer") CommandCloseProducer
y BaseCommand
x)
Bool
required'type'
130
-> do CommandCloseConsumer
y <- Parser CommandCloseConsumer
-> String -> Parser CommandCloseConsumer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandCloseConsumer -> Parser CommandCloseConsumer
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandCloseConsumer
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"close_consumer"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandCloseConsumer CommandCloseConsumer
-> CommandCloseConsumer -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "closeConsumer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"closeConsumer") CommandCloseConsumer
y BaseCommand
x)
Bool
required'type'
138
-> do CommandProducerSuccess
y <- Parser CommandProducerSuccess
-> String -> Parser CommandProducerSuccess
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandProducerSuccess -> Parser CommandProducerSuccess
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandProducerSuccess
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"producer_success"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandProducerSuccess
CommandProducerSuccess
-> CommandProducerSuccess -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "producerSuccess" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerSuccess") CommandProducerSuccess
y BaseCommand
x)
Bool
required'type'
146
-> do CommandPing
y <- Parser CommandPing -> String -> Parser CommandPing
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandPing -> Parser CommandPing
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandPing
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"ping"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandPing CommandPing
-> CommandPing -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "ping" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ping") CommandPing
y BaseCommand
x)
Bool
required'type'
154
-> do CommandPong
y <- Parser CommandPong -> String -> Parser CommandPong
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandPong -> Parser CommandPong
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandPong
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"pong"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandPong CommandPong
-> CommandPong -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "pong" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"pong") CommandPong
y BaseCommand
x)
Bool
required'type'
162
-> do CommandRedeliverUnacknowledgedMessages
y <- Parser CommandRedeliverUnacknowledgedMessages
-> String -> Parser CommandRedeliverUnacknowledgedMessages
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandRedeliverUnacknowledgedMessages
-> Parser CommandRedeliverUnacknowledgedMessages
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandRedeliverUnacknowledgedMessages
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"redeliverUnacknowledgedMessages"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> BaseCommand
-> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "redeliverUnacknowledgedMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"redeliverUnacknowledgedMessages")
CommandRedeliverUnacknowledgedMessages
y
BaseCommand
x)
Bool
required'type'
170
-> do CommandPartitionedTopicMetadata
y <- Parser CommandPartitionedTopicMetadata
-> String -> Parser CommandPartitionedTopicMetadata
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandPartitionedTopicMetadata
-> Parser CommandPartitionedTopicMetadata
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandPartitionedTopicMetadata
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"partitionMetadata"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionMetadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionMetadata") CommandPartitionedTopicMetadata
y BaseCommand
x)
Bool
required'type'
178
-> do CommandPartitionedTopicMetadataResponse
y <- Parser CommandPartitionedTopicMetadataResponse
-> String -> Parser CommandPartitionedTopicMetadataResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandPartitionedTopicMetadataResponse
-> Parser CommandPartitionedTopicMetadataResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandPartitionedTopicMetadataResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"partitionMetadataResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> BaseCommand
-> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionMetadataResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionMetadataResponse") CommandPartitionedTopicMetadataResponse
y BaseCommand
x)
Bool
required'type'
186
-> do CommandLookupTopic
y <- Parser CommandLookupTopic -> String -> Parser CommandLookupTopic
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandLookupTopic -> Parser CommandLookupTopic
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandLookupTopic
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"lookupTopic"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandLookupTopic CommandLookupTopic
-> CommandLookupTopic -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "lookupTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lookupTopic") CommandLookupTopic
y BaseCommand
x)
Bool
required'type'
194
-> do CommandLookupTopicResponse
y <- Parser CommandLookupTopicResponse
-> String -> Parser CommandLookupTopicResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandLookupTopicResponse
-> Parser CommandLookupTopicResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandLookupTopicResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"lookupTopicResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandLookupTopicResponse
CommandLookupTopicResponse
-> CommandLookupTopicResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "lookupTopicResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lookupTopicResponse") CommandLookupTopicResponse
y BaseCommand
x)
Bool
required'type'
202
-> do CommandConsumerStats
y <- Parser CommandConsumerStats
-> String -> Parser CommandConsumerStats
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandConsumerStats -> Parser CommandConsumerStats
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandConsumerStats
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"consumerStats"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandConsumerStats CommandConsumerStats
-> CommandConsumerStats -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "consumerStats" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerStats") CommandConsumerStats
y BaseCommand
x)
Bool
required'type'
210
-> do CommandConsumerStatsResponse
y <- Parser CommandConsumerStatsResponse
-> String -> Parser CommandConsumerStatsResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandConsumerStatsResponse
-> Parser CommandConsumerStatsResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandConsumerStatsResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"consumerStatsResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandConsumerStatsResponse
CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "consumerStatsResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerStatsResponse") CommandConsumerStatsResponse
y BaseCommand
x)
Bool
required'type'
218
-> do CommandReachedEndOfTopic
y <- Parser CommandReachedEndOfTopic
-> String -> Parser CommandReachedEndOfTopic
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandReachedEndOfTopic
-> Parser CommandReachedEndOfTopic
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandReachedEndOfTopic
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"reachedEndOfTopic"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandReachedEndOfTopic
CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "reachedEndOfTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"reachedEndOfTopic") CommandReachedEndOfTopic
y BaseCommand
x)
Bool
required'type'
226
-> do CommandSeek
y <- Parser CommandSeek -> String -> Parser CommandSeek
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandSeek -> Parser CommandSeek
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandSeek
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"seek"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandSeek CommandSeek
-> CommandSeek -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "seek" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"seek") CommandSeek
y BaseCommand
x)
Bool
required'type'
234
-> do CommandGetLastMessageId
y <- Parser CommandGetLastMessageId
-> String -> Parser CommandGetLastMessageId
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetLastMessageId -> Parser CommandGetLastMessageId
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetLastMessageId
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getLastMessageId"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetLastMessageId
CommandGetLastMessageId
-> CommandGetLastMessageId -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getLastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getLastMessageId") CommandGetLastMessageId
y BaseCommand
x)
Bool
required'type'
242
-> do CommandGetLastMessageIdResponse
y <- Parser CommandGetLastMessageIdResponse
-> String -> Parser CommandGetLastMessageIdResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetLastMessageIdResponse
-> Parser CommandGetLastMessageIdResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetLastMessageIdResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getLastMessageIdResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getLastMessageIdResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getLastMessageIdResponse") CommandGetLastMessageIdResponse
y BaseCommand
x)
Bool
required'type'
250
-> do CommandActiveConsumerChange
y <- Parser CommandActiveConsumerChange
-> String -> Parser CommandActiveConsumerChange
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandActiveConsumerChange
-> Parser CommandActiveConsumerChange
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandActiveConsumerChange
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"active_consumer_change"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandActiveConsumerChange
CommandActiveConsumerChange
-> CommandActiveConsumerChange -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "activeConsumerChange" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"activeConsumerChange") CommandActiveConsumerChange
y BaseCommand
x)
Bool
required'type'
258
-> do CommandGetTopicsOfNamespace
y <- Parser CommandGetTopicsOfNamespace
-> String -> Parser CommandGetTopicsOfNamespace
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetTopicsOfNamespace
-> Parser CommandGetTopicsOfNamespace
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetTopicsOfNamespace
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getTopicsOfNamespace"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getTopicsOfNamespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getTopicsOfNamespace") CommandGetTopicsOfNamespace
y BaseCommand
x)
Bool
required'type'
266
-> do CommandGetTopicsOfNamespaceResponse
y <- Parser CommandGetTopicsOfNamespaceResponse
-> String -> Parser CommandGetTopicsOfNamespaceResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetTopicsOfNamespaceResponse
-> Parser CommandGetTopicsOfNamespaceResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetTopicsOfNamespaceResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getTopicsOfNamespaceResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> BaseCommand
-> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getTopicsOfNamespaceResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getTopicsOfNamespaceResponse")
CommandGetTopicsOfNamespaceResponse
y
BaseCommand
x)
Bool
required'type'
274
-> do CommandGetSchema
y <- Parser CommandGetSchema -> String -> Parser CommandGetSchema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandGetSchema -> Parser CommandGetSchema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetSchema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getSchema"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandGetSchema CommandGetSchema
-> CommandGetSchema -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "getSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getSchema") CommandGetSchema
y BaseCommand
x)
Bool
required'type'
282
-> do CommandGetSchemaResponse
y <- Parser CommandGetSchemaResponse
-> String -> Parser CommandGetSchemaResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetSchemaResponse
-> Parser CommandGetSchemaResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetSchemaResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getSchemaResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetSchemaResponse
CommandGetSchemaResponse
-> CommandGetSchemaResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getSchemaResponse") CommandGetSchemaResponse
y BaseCommand
x)
Bool
required'type'
290
-> do CommandAuthChallenge
y <- Parser CommandAuthChallenge
-> String -> Parser CommandAuthChallenge
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandAuthChallenge -> Parser CommandAuthChallenge
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAuthChallenge
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"authChallenge"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandAuthChallenge CommandAuthChallenge
-> CommandAuthChallenge -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authChallenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authChallenge") CommandAuthChallenge
y BaseCommand
x)
Bool
required'type'
298
-> do CommandAuthResponse
y <- Parser CommandAuthResponse -> String -> Parser CommandAuthResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandAuthResponse -> Parser CommandAuthResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAuthResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"authResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandAuthResponse CommandAuthResponse
-> CommandAuthResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authResponse") CommandAuthResponse
y BaseCommand
x)
Bool
required'type'
306
-> do CommandAckResponse
y <- Parser CommandAckResponse -> String -> Parser CommandAckResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandAckResponse -> Parser CommandAckResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAckResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"ackResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandAckResponse CommandAckResponse
-> CommandAckResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "ackResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackResponse") CommandAckResponse
y BaseCommand
x)
Bool
required'type'
314
-> do CommandGetOrCreateSchema
y <- Parser CommandGetOrCreateSchema
-> String -> Parser CommandGetOrCreateSchema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetOrCreateSchema
-> Parser CommandGetOrCreateSchema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetOrCreateSchema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getOrCreateSchema"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetOrCreateSchema
CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getOrCreateSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getOrCreateSchema") CommandGetOrCreateSchema
y BaseCommand
x)
Bool
required'type'
322
-> do CommandGetOrCreateSchemaResponse
y <- Parser CommandGetOrCreateSchemaResponse
-> String -> Parser CommandGetOrCreateSchemaResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandGetOrCreateSchemaResponse
-> Parser CommandGetOrCreateSchemaResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandGetOrCreateSchemaResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"getOrCreateSchemaResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "getOrCreateSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"getOrCreateSchemaResponse") CommandGetOrCreateSchemaResponse
y BaseCommand
x)
Bool
required'type'
402
-> do CommandNewTxn
y <- Parser CommandNewTxn -> String -> Parser CommandNewTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandNewTxn -> Parser CommandNewTxn
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandNewTxn
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"newTxn"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandNewTxn CommandNewTxn
-> CommandNewTxn -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "newTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"newTxn") CommandNewTxn
y BaseCommand
x)
Bool
required'type'
410
-> do CommandNewTxnResponse
y <- Parser CommandNewTxnResponse
-> String -> Parser CommandNewTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandNewTxnResponse -> Parser CommandNewTxnResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandNewTxnResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"newTxnResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandNewTxnResponse CommandNewTxnResponse
-> CommandNewTxnResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "newTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"newTxnResponse") CommandNewTxnResponse
y BaseCommand
x)
Bool
required'type'
418
-> do CommandAddPartitionToTxn
y <- Parser CommandAddPartitionToTxn
-> String -> Parser CommandAddPartitionToTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandAddPartitionToTxn
-> Parser CommandAddPartitionToTxn
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAddPartitionToTxn
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"addPartitionToTxn"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandAddPartitionToTxn
CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "addPartitionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"addPartitionToTxn") CommandAddPartitionToTxn
y BaseCommand
x)
Bool
required'type'
426
-> do CommandAddPartitionToTxnResponse
y <- Parser CommandAddPartitionToTxnResponse
-> String -> Parser CommandAddPartitionToTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandAddPartitionToTxnResponse
-> Parser CommandAddPartitionToTxnResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAddPartitionToTxnResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"addPartitionToTxnResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "addPartitionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"addPartitionToTxnResponse") CommandAddPartitionToTxnResponse
y BaseCommand
x)
Bool
required'type'
434
-> do CommandAddSubscriptionToTxn
y <- Parser CommandAddSubscriptionToTxn
-> String -> Parser CommandAddSubscriptionToTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandAddSubscriptionToTxn
-> Parser CommandAddSubscriptionToTxn
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAddSubscriptionToTxn
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"addSubscriptionToTxn"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "addSubscriptionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"addSubscriptionToTxn") CommandAddSubscriptionToTxn
y BaseCommand
x)
Bool
required'type'
442
-> do CommandAddSubscriptionToTxnResponse
y <- Parser CommandAddSubscriptionToTxnResponse
-> String -> Parser CommandAddSubscriptionToTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandAddSubscriptionToTxnResponse
-> Parser CommandAddSubscriptionToTxnResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandAddSubscriptionToTxnResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"addSubscriptionToTxnResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> BaseCommand
-> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "addSubscriptionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"addSubscriptionToTxnResponse")
CommandAddSubscriptionToTxnResponse
y
BaseCommand
x)
Bool
required'type'
450
-> do CommandEndTxn
y <- Parser CommandEndTxn -> String -> Parser CommandEndTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandEndTxn -> Parser CommandEndTxn
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxn
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxn"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand CommandEndTxn CommandEndTxn
-> CommandEndTxn -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "endTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxn") CommandEndTxn
y BaseCommand
x)
Bool
required'type'
458
-> do CommandEndTxnResponse
y <- Parser CommandEndTxnResponse
-> String -> Parser CommandEndTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser CommandEndTxnResponse -> Parser CommandEndTxnResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxnResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxnResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand BaseCommand CommandEndTxnResponse CommandEndTxnResponse
-> CommandEndTxnResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "endTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxnResponse") CommandEndTxnResponse
y BaseCommand
x)
Bool
required'type'
466
-> do CommandEndTxnOnPartition
y <- Parser CommandEndTxnOnPartition
-> String -> Parser CommandEndTxnOnPartition
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandEndTxnOnPartition
-> Parser CommandEndTxnOnPartition
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxnOnPartition
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxnOnPartition"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandEndTxnOnPartition
CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "endTxnOnPartition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxnOnPartition") CommandEndTxnOnPartition
y BaseCommand
x)
Bool
required'type'
474
-> do CommandEndTxnOnPartitionResponse
y <- Parser CommandEndTxnOnPartitionResponse
-> String -> Parser CommandEndTxnOnPartitionResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandEndTxnOnPartitionResponse
-> Parser CommandEndTxnOnPartitionResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxnOnPartitionResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxnOnPartitionResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "endTxnOnPartitionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxnOnPartitionResponse") CommandEndTxnOnPartitionResponse
y BaseCommand
x)
Bool
required'type'
482
-> do CommandEndTxnOnSubscription
y <- Parser CommandEndTxnOnSubscription
-> String -> Parser CommandEndTxnOnSubscription
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandEndTxnOnSubscription
-> Parser CommandEndTxnOnSubscription
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxnOnSubscription
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxnOnSubscription"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "endTxnOnSubscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxnOnSubscription") CommandEndTxnOnSubscription
y BaseCommand
x)
Bool
required'type'
490
-> do CommandEndTxnOnSubscriptionResponse
y <- Parser CommandEndTxnOnSubscriptionResponse
-> String -> Parser CommandEndTxnOnSubscriptionResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser CommandEndTxnOnSubscriptionResponse
-> Parser CommandEndTxnOnSubscriptionResponse
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser CommandEndTxnOnSubscriptionResponse
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"endTxnOnSubscriptionResponse"
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter
BaseCommand
BaseCommand
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> BaseCommand
-> BaseCommand
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "endTxnOnSubscriptionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTxnOnSubscriptionResponse")
CommandEndTxnOnSubscriptionResponse
y
BaseCommand
x)
Bool
required'type'
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
BaseCommand -> Bool -> Parser BaseCommand
loop
(Setter BaseCommand BaseCommand FieldSet FieldSet
-> (FieldSet -> FieldSet) -> BaseCommand -> BaseCommand
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter BaseCommand BaseCommand FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) BaseCommand
x)
Bool
required'type'
in
Parser BaseCommand -> String -> Parser BaseCommand
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do BaseCommand -> Bool -> Parser BaseCommand
loop BaseCommand
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "BaseCommand"
buildMessage :: BaseCommand -> Builder
buildMessage
= \ _x :: BaseCommand
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
((Int -> Builder)
-> (BaseCommand'Type -> Int) -> BaseCommand'Type -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
BaseCommand'Type -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
BaseCommand'Type
BaseCommand
BaseCommand
BaseCommand'Type
BaseCommand'Type
-> BaseCommand -> BaseCommand'Type
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'") BaseCommand
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandConnect)
BaseCommand
BaseCommand
(Maybe CommandConnect)
(Maybe CommandConnect)
-> BaseCommand -> Maybe CommandConnect
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'connect" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'connect") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandConnect
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (CommandConnect -> ByteString) -> CommandConnect -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandConnect -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandConnect
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandConnected)
BaseCommand
BaseCommand
(Maybe CommandConnected)
(Maybe CommandConnected)
-> BaseCommand -> Maybe CommandConnected
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'connected" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'connected") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandConnected
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (CommandConnected -> ByteString) -> CommandConnected -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandConnected -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandConnected
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSubscribe)
BaseCommand
BaseCommand
(Maybe CommandSubscribe)
(Maybe CommandSubscribe)
-> BaseCommand -> Maybe CommandSubscribe
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'subscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'subscribe") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSubscribe
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder)
-> (CommandSubscribe -> ByteString) -> CommandSubscribe -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandSubscribe -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSubscribe
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandProducer)
BaseCommand
BaseCommand
(Maybe CommandProducer)
(Maybe CommandProducer)
-> BaseCommand -> Maybe CommandProducer
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'producer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'producer") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandProducer
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder)
-> (CommandProducer -> ByteString) -> CommandProducer -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandProducer -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandProducer
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSend)
BaseCommand
BaseCommand
(Maybe CommandSend)
(Maybe CommandSend)
-> BaseCommand -> Maybe CommandSend
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'send" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'send") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSend
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder)
-> (CommandSend -> ByteString) -> CommandSend -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandSend -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSend
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSendReceipt)
BaseCommand
BaseCommand
(Maybe CommandSendReceipt)
(Maybe CommandSendReceipt)
-> BaseCommand -> Maybe CommandSendReceipt
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'sendReceipt" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sendReceipt") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSendReceipt
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder)
-> (CommandSendReceipt -> ByteString)
-> CommandSendReceipt
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandSendReceipt -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSendReceipt
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSendError)
BaseCommand
BaseCommand
(Maybe CommandSendError)
(Maybe CommandSendError)
-> BaseCommand -> Maybe CommandSendError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'sendError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sendError") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSendError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 66)
((ByteString -> Builder)
-> (CommandSendError -> ByteString) -> CommandSendError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
CommandSendError -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSendError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandMessage)
BaseCommand
BaseCommand
(Maybe CommandMessage)
(Maybe CommandMessage)
-> BaseCommand -> Maybe CommandMessage
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandMessage
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 74)
((ByteString -> Builder)
-> (CommandMessage -> ByteString) -> CommandMessage -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandMessage -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandMessage
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAck)
BaseCommand
BaseCommand
(Maybe CommandAck)
(Maybe CommandAck)
-> BaseCommand -> Maybe CommandAck
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'ack" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'ack") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAck
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 82)
((ByteString -> Builder)
-> (CommandAck -> ByteString) -> CommandAck -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAck -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAck
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandFlow)
BaseCommand
BaseCommand
(Maybe CommandFlow)
(Maybe CommandFlow)
-> BaseCommand -> Maybe CommandFlow
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'flow" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'flow") BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandFlow
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 90)
((ByteString -> Builder)
-> (CommandFlow -> ByteString) -> CommandFlow -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandFlow -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandFlow
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandUnsubscribe)
BaseCommand
BaseCommand
(Maybe CommandUnsubscribe)
(Maybe CommandUnsubscribe)
-> BaseCommand -> Maybe CommandUnsubscribe
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'unsubscribe" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'unsubscribe")
BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandUnsubscribe
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 98)
((ByteString -> Builder)
-> (CommandUnsubscribe -> ByteString)
-> CommandUnsubscribe
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandUnsubscribe -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandUnsubscribe
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSuccess)
BaseCommand
BaseCommand
(Maybe CommandSuccess)
(Maybe CommandSuccess)
-> BaseCommand -> Maybe CommandSuccess
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'success" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'success")
BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSuccess
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
106)
((ByteString -> Builder)
-> (CommandSuccess -> ByteString) -> CommandSuccess -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandSuccess -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSuccess
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandError)
BaseCommand
BaseCommand
(Maybe CommandError)
(Maybe CommandError)
-> BaseCommand -> Maybe CommandError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'error")
BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
114)
((ByteString -> Builder)
-> (CommandError -> ByteString) -> CommandError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandError -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandCloseProducer)
BaseCommand
BaseCommand
(Maybe CommandCloseProducer)
(Maybe CommandCloseProducer)
-> BaseCommand -> Maybe CommandCloseProducer
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'closeProducer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'closeProducer")
BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandCloseProducer
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
122)
((ByteString -> Builder)
-> (CommandCloseProducer -> ByteString)
-> CommandCloseProducer
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandCloseProducer -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandCloseProducer
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandCloseConsumer)
BaseCommand
BaseCommand
(Maybe CommandCloseConsumer)
(Maybe CommandCloseConsumer)
-> BaseCommand -> Maybe CommandCloseConsumer
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'closeConsumer" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'closeConsumer")
BaseCommand
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandCloseConsumer
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
130)
((ByteString -> Builder)
-> (CommandCloseConsumer -> ByteString)
-> CommandCloseConsumer
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandCloseConsumer -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandCloseConsumer
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandProducerSuccess)
BaseCommand
BaseCommand
(Maybe CommandProducerSuccess)
(Maybe CommandProducerSuccess)
-> BaseCommand -> Maybe CommandProducerSuccess
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'producerSuccess" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'producerSuccess")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandProducerSuccess
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
138)
((ByteString -> Builder)
-> (CommandProducerSuccess -> ByteString)
-> CommandProducerSuccess
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandProducerSuccess -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandProducerSuccess
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandPing)
BaseCommand
BaseCommand
(Maybe CommandPing)
(Maybe CommandPing)
-> BaseCommand -> Maybe CommandPing
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'ping" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'ping")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandPing
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
146)
((ByteString -> Builder)
-> (CommandPing -> ByteString) -> CommandPing -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandPing -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandPing
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandPong)
BaseCommand
BaseCommand
(Maybe CommandPong)
(Maybe CommandPong)
-> BaseCommand -> Maybe CommandPong
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'pong" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'pong")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandPong
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
154)
((ByteString -> Builder)
-> (CommandPong -> ByteString) -> CommandPong -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandPong -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandPong
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandRedeliverUnacknowledgedMessages)
BaseCommand
BaseCommand
(Maybe CommandRedeliverUnacknowledgedMessages)
(Maybe CommandRedeliverUnacknowledgedMessages)
-> BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'redeliverUnacknowledgedMessages" a,
Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'redeliverUnacknowledgedMessages")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandRedeliverUnacknowledgedMessages
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
162)
((ByteString -> Builder)
-> (CommandRedeliverUnacknowledgedMessages -> ByteString)
-> CommandRedeliverUnacknowledgedMessages
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandRedeliverUnacknowledgedMessages -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandRedeliverUnacknowledgedMessages
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandPartitionedTopicMetadata)
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadata)
(Maybe CommandPartitionedTopicMetadata)
-> BaseCommand -> Maybe CommandPartitionedTopicMetadata
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionMetadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'partitionMetadata")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandPartitionedTopicMetadata
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
170)
((ByteString -> Builder)
-> (CommandPartitionedTopicMetadata -> ByteString)
-> CommandPartitionedTopicMetadata
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandPartitionedTopicMetadata -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandPartitionedTopicMetadata
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandPartitionedTopicMetadataResponse)
BaseCommand
BaseCommand
(Maybe CommandPartitionedTopicMetadataResponse)
(Maybe CommandPartitionedTopicMetadataResponse)
-> BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionMetadataResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'partitionMetadataResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandPartitionedTopicMetadataResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
178)
((ByteString -> Builder)
-> (CommandPartitionedTopicMetadataResponse -> ByteString)
-> CommandPartitionedTopicMetadataResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandPartitionedTopicMetadataResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandPartitionedTopicMetadataResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandLookupTopic)
BaseCommand
BaseCommand
(Maybe CommandLookupTopic)
(Maybe CommandLookupTopic)
-> BaseCommand -> Maybe CommandLookupTopic
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'lookupTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'lookupTopic")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandLookupTopic
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
186)
((ByteString -> Builder)
-> (CommandLookupTopic -> ByteString)
-> CommandLookupTopic
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandLookupTopic -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandLookupTopic
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandLookupTopicResponse)
BaseCommand
BaseCommand
(Maybe CommandLookupTopicResponse)
(Maybe CommandLookupTopicResponse)
-> BaseCommand -> Maybe CommandLookupTopicResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'lookupTopicResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'lookupTopicResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandLookupTopicResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
194)
((ByteString -> Builder)
-> (CommandLookupTopicResponse -> ByteString)
-> CommandLookupTopicResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandLookupTopicResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandLookupTopicResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandConsumerStats)
BaseCommand
BaseCommand
(Maybe CommandConsumerStats)
(Maybe CommandConsumerStats)
-> BaseCommand -> Maybe CommandConsumerStats
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'consumerStats" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'consumerStats")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandConsumerStats
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
202)
((ByteString -> Builder)
-> (CommandConsumerStats -> ByteString)
-> CommandConsumerStats
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandConsumerStats -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandConsumerStats
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandConsumerStatsResponse)
BaseCommand
BaseCommand
(Maybe CommandConsumerStatsResponse)
(Maybe CommandConsumerStatsResponse)
-> BaseCommand -> Maybe CommandConsumerStatsResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'consumerStatsResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'consumerStatsResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandConsumerStatsResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
210)
((ByteString -> Builder)
-> (CommandConsumerStatsResponse -> ByteString)
-> CommandConsumerStatsResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandConsumerStatsResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandConsumerStatsResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandReachedEndOfTopic)
BaseCommand
BaseCommand
(Maybe CommandReachedEndOfTopic)
(Maybe CommandReachedEndOfTopic)
-> BaseCommand -> Maybe CommandReachedEndOfTopic
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'reachedEndOfTopic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'reachedEndOfTopic")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandReachedEndOfTopic
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
218)
((ByteString -> Builder)
-> (CommandReachedEndOfTopic -> ByteString)
-> CommandReachedEndOfTopic
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandReachedEndOfTopic -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandReachedEndOfTopic
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSeek)
BaseCommand
BaseCommand
(Maybe CommandSeek)
(Maybe CommandSeek)
-> BaseCommand -> Maybe CommandSeek
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'seek" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'seek")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSeek
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
226)
((ByteString -> Builder)
-> (CommandSeek -> ByteString) -> CommandSeek -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandSeek -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandSeek
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetLastMessageId)
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageId)
(Maybe CommandGetLastMessageId)
-> BaseCommand -> Maybe CommandGetLastMessageId
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getLastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getLastMessageId")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetLastMessageId
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
234)
((ByteString -> Builder)
-> (CommandGetLastMessageId -> ByteString)
-> CommandGetLastMessageId
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetLastMessageId -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetLastMessageId
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetLastMessageIdResponse)
BaseCommand
BaseCommand
(Maybe CommandGetLastMessageIdResponse)
(Maybe CommandGetLastMessageIdResponse)
-> BaseCommand -> Maybe CommandGetLastMessageIdResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getLastMessageIdResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getLastMessageIdResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetLastMessageIdResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
242)
((ByteString -> Builder)
-> (CommandGetLastMessageIdResponse -> ByteString)
-> CommandGetLastMessageIdResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetLastMessageIdResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetLastMessageIdResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandActiveConsumerChange)
BaseCommand
BaseCommand
(Maybe CommandActiveConsumerChange)
(Maybe CommandActiveConsumerChange)
-> BaseCommand -> Maybe CommandActiveConsumerChange
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'activeConsumerChange" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'activeConsumerChange")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandActiveConsumerChange
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
250)
((ByteString -> Builder)
-> (CommandActiveConsumerChange -> ByteString)
-> CommandActiveConsumerChange
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandActiveConsumerChange -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandActiveConsumerChange
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetTopicsOfNamespace)
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespace)
(Maybe CommandGetTopicsOfNamespace)
-> BaseCommand -> Maybe CommandGetTopicsOfNamespace
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getTopicsOfNamespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getTopicsOfNamespace")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetTopicsOfNamespace
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
258)
((ByteString -> Builder)
-> (CommandGetTopicsOfNamespace -> ByteString)
-> CommandGetTopicsOfNamespace
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetTopicsOfNamespace -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetTopicsOfNamespace
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetTopicsOfNamespaceResponse)
BaseCommand
BaseCommand
(Maybe CommandGetTopicsOfNamespaceResponse)
(Maybe CommandGetTopicsOfNamespaceResponse)
-> BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getTopicsOfNamespaceResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getTopicsOfNamespaceResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetTopicsOfNamespaceResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
266)
((ByteString -> Builder)
-> (CommandGetTopicsOfNamespaceResponse -> ByteString)
-> CommandGetTopicsOfNamespaceResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetTopicsOfNamespaceResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetTopicsOfNamespaceResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetSchema)
BaseCommand
BaseCommand
(Maybe CommandGetSchema)
(Maybe CommandGetSchema)
-> BaseCommand -> Maybe CommandGetSchema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getSchema")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetSchema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
274)
((ByteString -> Builder)
-> (CommandGetSchema -> ByteString) -> CommandGetSchema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetSchema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetSchema
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetSchemaResponse)
BaseCommand
BaseCommand
(Maybe CommandGetSchemaResponse)
(Maybe CommandGetSchemaResponse)
-> BaseCommand -> Maybe CommandGetSchemaResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getSchemaResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetSchemaResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
282)
((ByteString -> Builder)
-> (CommandGetSchemaResponse -> ByteString)
-> CommandGetSchemaResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetSchemaResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetSchemaResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAuthChallenge)
BaseCommand
BaseCommand
(Maybe CommandAuthChallenge)
(Maybe CommandAuthChallenge)
-> BaseCommand -> Maybe CommandAuthChallenge
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authChallenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'authChallenge")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAuthChallenge
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
290)
((ByteString -> Builder)
-> (CommandAuthChallenge -> ByteString)
-> CommandAuthChallenge
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAuthChallenge -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAuthChallenge
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAuthResponse)
BaseCommand
BaseCommand
(Maybe CommandAuthResponse)
(Maybe CommandAuthResponse)
-> BaseCommand -> Maybe CommandAuthResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'authResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAuthResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
298)
((ByteString -> Builder)
-> (CommandAuthResponse -> ByteString)
-> CommandAuthResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAuthResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAuthResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAckResponse)
BaseCommand
BaseCommand
(Maybe CommandAckResponse)
(Maybe CommandAckResponse)
-> BaseCommand -> Maybe CommandAckResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'ackResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'ackResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAckResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
306)
((ByteString -> Builder)
-> (CommandAckResponse -> ByteString)
-> CommandAckResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAckResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAckResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetOrCreateSchema)
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchema)
(Maybe CommandGetOrCreateSchema)
-> BaseCommand -> Maybe CommandGetOrCreateSchema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getOrCreateSchema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getOrCreateSchema")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetOrCreateSchema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
314)
((ByteString -> Builder)
-> (CommandGetOrCreateSchema -> ByteString)
-> CommandGetOrCreateSchema
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetOrCreateSchema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetOrCreateSchema
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetOrCreateSchemaResponse)
BaseCommand
BaseCommand
(Maybe CommandGetOrCreateSchemaResponse)
(Maybe CommandGetOrCreateSchemaResponse)
-> BaseCommand -> Maybe CommandGetOrCreateSchemaResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'getOrCreateSchemaResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'getOrCreateSchemaResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetOrCreateSchemaResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
322)
((ByteString -> Builder)
-> (CommandGetOrCreateSchemaResponse -> ByteString)
-> CommandGetOrCreateSchemaResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandGetOrCreateSchemaResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandGetOrCreateSchemaResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandNewTxn)
BaseCommand
BaseCommand
(Maybe CommandNewTxn)
(Maybe CommandNewTxn)
-> BaseCommand -> Maybe CommandNewTxn
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'newTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'newTxn")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandNewTxn
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
402)
((ByteString -> Builder)
-> (CommandNewTxn -> ByteString) -> CommandNewTxn -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandNewTxn -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandNewTxn
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandNewTxnResponse)
BaseCommand
BaseCommand
(Maybe CommandNewTxnResponse)
(Maybe CommandNewTxnResponse)
-> BaseCommand -> Maybe CommandNewTxnResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'newTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'newTxnResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandNewTxnResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
410)
((ByteString -> Builder)
-> (CommandNewTxnResponse -> ByteString)
-> CommandNewTxnResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandNewTxnResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandNewTxnResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAddPartitionToTxn)
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxn)
(Maybe CommandAddPartitionToTxn)
-> BaseCommand -> Maybe CommandAddPartitionToTxn
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'addPartitionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'addPartitionToTxn")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAddPartitionToTxn
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
418)
((ByteString -> Builder)
-> (CommandAddPartitionToTxn -> ByteString)
-> CommandAddPartitionToTxn
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAddPartitionToTxn -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAddPartitionToTxn
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAddPartitionToTxnResponse)
BaseCommand
BaseCommand
(Maybe CommandAddPartitionToTxnResponse)
(Maybe CommandAddPartitionToTxnResponse)
-> BaseCommand -> Maybe CommandAddPartitionToTxnResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'addPartitionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'addPartitionToTxnResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAddPartitionToTxnResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
426)
((ByteString -> Builder)
-> (CommandAddPartitionToTxnResponse -> ByteString)
-> CommandAddPartitionToTxnResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAddPartitionToTxnResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAddPartitionToTxnResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAddSubscriptionToTxn)
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxn)
(Maybe CommandAddSubscriptionToTxn)
-> BaseCommand -> Maybe CommandAddSubscriptionToTxn
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'addSubscriptionToTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'addSubscriptionToTxn")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAddSubscriptionToTxn
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
434)
((ByteString -> Builder)
-> (CommandAddSubscriptionToTxn -> ByteString)
-> CommandAddSubscriptionToTxn
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAddSubscriptionToTxn -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAddSubscriptionToTxn
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAddSubscriptionToTxnResponse)
BaseCommand
BaseCommand
(Maybe CommandAddSubscriptionToTxnResponse)
(Maybe CommandAddSubscriptionToTxnResponse)
-> BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'addSubscriptionToTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'addSubscriptionToTxnResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAddSubscriptionToTxnResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
442)
((ByteString -> Builder)
-> (CommandAddSubscriptionToTxnResponse -> ByteString)
-> CommandAddSubscriptionToTxnResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandAddSubscriptionToTxnResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandAddSubscriptionToTxnResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxn)
BaseCommand
BaseCommand
(Maybe CommandEndTxn)
(Maybe CommandEndTxn)
-> BaseCommand -> Maybe CommandEndTxn
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxn" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxn")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxn
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
450)
((ByteString -> Builder)
-> (CommandEndTxn -> ByteString) -> CommandEndTxn -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxn -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxn
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxnResponse)
BaseCommand
BaseCommand
(Maybe CommandEndTxnResponse)
(Maybe CommandEndTxnResponse)
-> BaseCommand -> Maybe CommandEndTxnResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxnResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
458)
((ByteString -> Builder)
-> (CommandEndTxnResponse -> ByteString)
-> CommandEndTxnResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxnResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxnResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxnOnPartition)
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartition)
(Maybe CommandEndTxnOnPartition)
-> BaseCommand -> Maybe CommandEndTxnOnPartition
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnPartition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnOnPartition")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxnOnPartition
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
466)
((ByteString -> Builder)
-> (CommandEndTxnOnPartition -> ByteString)
-> CommandEndTxnOnPartition
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxnOnPartition -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxnOnPartition
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxnOnPartitionResponse)
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnPartitionResponse)
(Maybe CommandEndTxnOnPartitionResponse)
-> BaseCommand -> Maybe CommandEndTxnOnPartitionResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnPartitionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnOnPartitionResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxnOnPartitionResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
474)
((ByteString -> Builder)
-> (CommandEndTxnOnPartitionResponse -> ByteString)
-> CommandEndTxnOnPartitionResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxnOnPartitionResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxnOnPartitionResponse
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxnOnSubscription)
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscription)
(Maybe CommandEndTxnOnSubscription)
-> BaseCommand -> Maybe CommandEndTxnOnSubscription
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnSubscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnOnSubscription")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxnOnSubscription
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
482)
((ByteString -> Builder)
-> (CommandEndTxnOnSubscription -> ByteString)
-> CommandEndTxnOnSubscription
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxnOnSubscription -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxnOnSubscription
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandEndTxnOnSubscriptionResponse)
BaseCommand
BaseCommand
(Maybe CommandEndTxnOnSubscriptionResponse)
(Maybe CommandEndTxnOnSubscriptionResponse)
-> BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'endTxnOnSubscriptionResponse" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'endTxnOnSubscriptionResponse")
BaseCommand
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandEndTxnOnSubscriptionResponse
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
490)
((ByteString -> Builder)
-> (CommandEndTxnOnSubscriptionResponse -> ByteString)
-> CommandEndTxnOnSubscriptionResponse
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
CommandEndTxnOnSubscriptionResponse -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
CommandEndTxnOnSubscriptionResponse
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet BaseCommand BaseCommand FieldSet FieldSet
-> BaseCommand -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike FieldSet BaseCommand BaseCommand FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields
BaseCommand
_x)))))))))))))))))))))))))))))))))))))))))))))))))))))
instance Control.DeepSeq.NFData BaseCommand where
rnf :: BaseCommand -> ()
rnf
= \ x__ :: BaseCommand
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> FieldSet
_BaseCommand'_unknownFields BaseCommand
x__)
(BaseCommand'Type -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> BaseCommand'Type
_BaseCommand'type' BaseCommand
x__)
(Maybe CommandConnect -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandConnect
_BaseCommand'connect BaseCommand
x__)
(Maybe CommandConnected -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandConnected
_BaseCommand'connected BaseCommand
x__)
(Maybe CommandSubscribe -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSubscribe
_BaseCommand'subscribe BaseCommand
x__)
(Maybe CommandProducer -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandProducer
_BaseCommand'producer BaseCommand
x__)
(Maybe CommandSend -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSend
_BaseCommand'send BaseCommand
x__)
(Maybe CommandSendReceipt -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSendReceipt
_BaseCommand'sendReceipt BaseCommand
x__)
(Maybe CommandSendError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSendError
_BaseCommand'sendError BaseCommand
x__)
(Maybe CommandMessage -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandMessage
_BaseCommand'message BaseCommand
x__)
(Maybe CommandAck -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAck
_BaseCommand'ack BaseCommand
x__)
(Maybe CommandFlow -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandFlow
_BaseCommand'flow BaseCommand
x__)
(Maybe CommandUnsubscribe -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandUnsubscribe
_BaseCommand'unsubscribe BaseCommand
x__)
(Maybe CommandSuccess -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSuccess
_BaseCommand'success BaseCommand
x__)
(Maybe CommandError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandError
_BaseCommand'error BaseCommand
x__)
(Maybe CommandCloseProducer -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandCloseProducer
_BaseCommand'closeProducer BaseCommand
x__)
(Maybe CommandCloseConsumer -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandCloseConsumer
_BaseCommand'closeConsumer BaseCommand
x__)
(Maybe CommandProducerSuccess -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandProducerSuccess
_BaseCommand'producerSuccess BaseCommand
x__)
(Maybe CommandPing -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandPing
_BaseCommand'ping BaseCommand
x__)
(Maybe CommandPong -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandPong
_BaseCommand'pong BaseCommand
x__)
(Maybe CommandRedeliverUnacknowledgedMessages -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandRedeliverUnacknowledgedMessages
_BaseCommand'redeliverUnacknowledgedMessages
BaseCommand
x__)
(Maybe CommandPartitionedTopicMetadata -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandPartitionedTopicMetadata
_BaseCommand'partitionMetadata
BaseCommand
x__)
(Maybe CommandPartitionedTopicMetadataResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandPartitionedTopicMetadataResponse
_BaseCommand'partitionMetadataResponse
BaseCommand
x__)
(Maybe CommandLookupTopic -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandLookupTopic
_BaseCommand'lookupTopic
BaseCommand
x__)
(Maybe CommandLookupTopicResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandLookupTopicResponse
_BaseCommand'lookupTopicResponse
BaseCommand
x__)
(Maybe CommandConsumerStats -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandConsumerStats
_BaseCommand'consumerStats
BaseCommand
x__)
(Maybe CommandConsumerStatsResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandConsumerStatsResponse
_BaseCommand'consumerStatsResponse
BaseCommand
x__)
(Maybe CommandReachedEndOfTopic -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandReachedEndOfTopic
_BaseCommand'reachedEndOfTopic
BaseCommand
x__)
(Maybe CommandSeek -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandSeek
_BaseCommand'seek
BaseCommand
x__)
(Maybe CommandGetLastMessageId -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetLastMessageId
_BaseCommand'getLastMessageId
BaseCommand
x__)
(Maybe CommandGetLastMessageIdResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetLastMessageIdResponse
_BaseCommand'getLastMessageIdResponse
BaseCommand
x__)
(Maybe CommandActiveConsumerChange -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandActiveConsumerChange
_BaseCommand'activeConsumerChange
BaseCommand
x__)
(Maybe CommandGetTopicsOfNamespace -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetTopicsOfNamespace
_BaseCommand'getTopicsOfNamespace
BaseCommand
x__)
(Maybe CommandGetTopicsOfNamespaceResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetTopicsOfNamespaceResponse
_BaseCommand'getTopicsOfNamespaceResponse
BaseCommand
x__)
(Maybe CommandGetSchema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetSchema
_BaseCommand'getSchema
BaseCommand
x__)
(Maybe CommandGetSchemaResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetSchemaResponse
_BaseCommand'getSchemaResponse
BaseCommand
x__)
(Maybe CommandAuthChallenge -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAuthChallenge
_BaseCommand'authChallenge
BaseCommand
x__)
(Maybe CommandAuthResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAuthResponse
_BaseCommand'authResponse
BaseCommand
x__)
(Maybe CommandAckResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAckResponse
_BaseCommand'ackResponse
BaseCommand
x__)
(Maybe CommandGetOrCreateSchema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetOrCreateSchema
_BaseCommand'getOrCreateSchema
BaseCommand
x__)
(Maybe CommandGetOrCreateSchemaResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandGetOrCreateSchemaResponse
_BaseCommand'getOrCreateSchemaResponse
BaseCommand
x__)
(Maybe CommandNewTxn -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandNewTxn
_BaseCommand'newTxn
BaseCommand
x__)
(Maybe CommandNewTxnResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandNewTxnResponse
_BaseCommand'newTxnResponse
BaseCommand
x__)
(Maybe CommandAddPartitionToTxn -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAddPartitionToTxn
_BaseCommand'addPartitionToTxn
BaseCommand
x__)
(Maybe CommandAddPartitionToTxnResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAddPartitionToTxnResponse
_BaseCommand'addPartitionToTxnResponse
BaseCommand
x__)
(Maybe CommandAddSubscriptionToTxn -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAddSubscriptionToTxn
_BaseCommand'addSubscriptionToTxn
BaseCommand
x__)
(Maybe CommandAddSubscriptionToTxnResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandAddSubscriptionToTxnResponse
_BaseCommand'addSubscriptionToTxnResponse
BaseCommand
x__)
(Maybe CommandEndTxn -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxn
_BaseCommand'endTxn
BaseCommand
x__)
(Maybe CommandEndTxnResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxnResponse
_BaseCommand'endTxnResponse
BaseCommand
x__)
(Maybe CommandEndTxnOnPartition -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxnOnPartition
_BaseCommand'endTxnOnPartition
BaseCommand
x__)
(Maybe CommandEndTxnOnPartitionResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxnOnPartitionResponse
_BaseCommand'endTxnOnPartitionResponse
BaseCommand
x__)
(Maybe CommandEndTxnOnSubscription -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxnOnSubscription
_BaseCommand'endTxnOnSubscription
BaseCommand
x__)
(Maybe CommandEndTxnOnSubscriptionResponse -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BaseCommand -> Maybe CommandEndTxnOnSubscriptionResponse
_BaseCommand'endTxnOnSubscriptionResponse
BaseCommand
x__)
()))))))))))))))))))))))))))))))))))))))))))))))))))))
data BaseCommand'Type
= BaseCommand'CONNECT |
BaseCommand'CONNECTED |
BaseCommand'SUBSCRIBE |
BaseCommand'PRODUCER |
BaseCommand'SEND |
BaseCommand'SEND_RECEIPT |
BaseCommand'SEND_ERROR |
BaseCommand'MESSAGE |
BaseCommand'ACK |
BaseCommand'FLOW |
BaseCommand'UNSUBSCRIBE |
BaseCommand'SUCCESS |
BaseCommand'ERROR |
BaseCommand'CLOSE_PRODUCER |
BaseCommand'CLOSE_CONSUMER |
BaseCommand'PRODUCER_SUCCESS |
BaseCommand'PING |
BaseCommand'PONG |
BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES |
BaseCommand'PARTITIONED_METADATA |
BaseCommand'PARTITIONED_METADATA_RESPONSE |
BaseCommand'LOOKUP |
BaseCommand'LOOKUP_RESPONSE |
BaseCommand'CONSUMER_STATS |
BaseCommand'CONSUMER_STATS_RESPONSE |
BaseCommand'REACHED_END_OF_TOPIC |
BaseCommand'SEEK |
BaseCommand'GET_LAST_MESSAGE_ID |
BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE |
BaseCommand'ACTIVE_CONSUMER_CHANGE |
BaseCommand'GET_TOPICS_OF_NAMESPACE |
BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE |
BaseCommand'GET_SCHEMA |
BaseCommand'GET_SCHEMA_RESPONSE |
BaseCommand'AUTH_CHALLENGE |
BaseCommand'AUTH_RESPONSE |
BaseCommand'ACK_RESPONSE |
BaseCommand'GET_OR_CREATE_SCHEMA |
BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE |
BaseCommand'NEW_TXN |
BaseCommand'NEW_TXN_RESPONSE |
BaseCommand'ADD_PARTITION_TO_TXN |
BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE |
BaseCommand'ADD_SUBSCRIPTION_TO_TXN |
BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE |
BaseCommand'END_TXN |
BaseCommand'END_TXN_RESPONSE |
BaseCommand'END_TXN_ON_PARTITION |
BaseCommand'END_TXN_ON_PARTITION_RESPONSE |
BaseCommand'END_TXN_ON_SUBSCRIPTION |
BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
deriving stock (Int -> BaseCommand'Type -> ShowS
[BaseCommand'Type] -> ShowS
BaseCommand'Type -> String
(Int -> BaseCommand'Type -> ShowS)
-> (BaseCommand'Type -> String)
-> ([BaseCommand'Type] -> ShowS)
-> Show BaseCommand'Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BaseCommand'Type] -> ShowS
$cshowList :: [BaseCommand'Type] -> ShowS
show :: BaseCommand'Type -> String
$cshow :: BaseCommand'Type -> String
showsPrec :: Int -> BaseCommand'Type -> ShowS
$cshowsPrec :: Int -> BaseCommand'Type -> ShowS
Prelude.Show, BaseCommand'Type -> BaseCommand'Type -> Bool
(BaseCommand'Type -> BaseCommand'Type -> Bool)
-> (BaseCommand'Type -> BaseCommand'Type -> Bool)
-> Eq BaseCommand'Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c/= :: BaseCommand'Type -> BaseCommand'Type -> Bool
== :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c== :: BaseCommand'Type -> BaseCommand'Type -> Bool
Prelude.Eq, Eq BaseCommand'Type
Eq BaseCommand'Type =>
(BaseCommand'Type -> BaseCommand'Type -> Ordering)
-> (BaseCommand'Type -> BaseCommand'Type -> Bool)
-> (BaseCommand'Type -> BaseCommand'Type -> Bool)
-> (BaseCommand'Type -> BaseCommand'Type -> Bool)
-> (BaseCommand'Type -> BaseCommand'Type -> Bool)
-> (BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type)
-> (BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type)
-> Ord BaseCommand'Type
BaseCommand'Type -> BaseCommand'Type -> Bool
BaseCommand'Type -> BaseCommand'Type -> Ordering
BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type
$cmin :: BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type
max :: BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type
$cmax :: BaseCommand'Type -> BaseCommand'Type -> BaseCommand'Type
>= :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c>= :: BaseCommand'Type -> BaseCommand'Type -> Bool
> :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c> :: BaseCommand'Type -> BaseCommand'Type -> Bool
<= :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c<= :: BaseCommand'Type -> BaseCommand'Type -> Bool
< :: BaseCommand'Type -> BaseCommand'Type -> Bool
$c< :: BaseCommand'Type -> BaseCommand'Type -> Bool
compare :: BaseCommand'Type -> BaseCommand'Type -> Ordering
$ccompare :: BaseCommand'Type -> BaseCommand'Type -> Ordering
$cp1Ord :: Eq BaseCommand'Type
Prelude.Ord)
instance Data.ProtoLens.MessageEnum BaseCommand'Type where
maybeToEnum :: Int -> Maybe BaseCommand'Type
maybeToEnum 2 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONNECT
maybeToEnum 3 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONNECTED
maybeToEnum 4 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SUBSCRIBE
maybeToEnum 5 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PRODUCER
maybeToEnum 6 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND
maybeToEnum 7 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND_RECEIPT
maybeToEnum 8 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND_ERROR
maybeToEnum 9 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'MESSAGE
maybeToEnum 10 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACK
maybeToEnum 11 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'FLOW
maybeToEnum 12 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'UNSUBSCRIBE
maybeToEnum 13 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SUCCESS
maybeToEnum 14 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ERROR
maybeToEnum 15 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CLOSE_PRODUCER
maybeToEnum 16 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CLOSE_CONSUMER
maybeToEnum 17 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PRODUCER_SUCCESS
maybeToEnum 18 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PING
maybeToEnum 19 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PONG
maybeToEnum 20
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
maybeToEnum 21 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PARTITIONED_METADATA
maybeToEnum 22
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PARTITIONED_METADATA_RESPONSE
maybeToEnum 23 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'LOOKUP
maybeToEnum 24 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'LOOKUP_RESPONSE
maybeToEnum 25 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONSUMER_STATS
maybeToEnum 26 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONSUMER_STATS_RESPONSE
maybeToEnum 27 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'REACHED_END_OF_TOPIC
maybeToEnum 28 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEEK
maybeToEnum 29 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID
maybeToEnum 30
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
maybeToEnum 31 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACTIVE_CONSUMER_CHANGE
maybeToEnum 32 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE
maybeToEnum 33
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
maybeToEnum 34 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_SCHEMA
maybeToEnum 35 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_SCHEMA_RESPONSE
maybeToEnum 36 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'AUTH_CHALLENGE
maybeToEnum 37 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'AUTH_RESPONSE
maybeToEnum 38 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACK_RESPONSE
maybeToEnum 39 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA
maybeToEnum 40
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
maybeToEnum 50 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'NEW_TXN
maybeToEnum 51 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'NEW_TXN_RESPONSE
maybeToEnum 52 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN
maybeToEnum 53
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
maybeToEnum 54 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN
maybeToEnum 55
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
maybeToEnum 56 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN
maybeToEnum 57 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_RESPONSE
maybeToEnum 58 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION
maybeToEnum 59
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION_RESPONSE
maybeToEnum 60 = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION
maybeToEnum 61
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
maybeToEnum _ = Maybe BaseCommand'Type
forall a. Maybe a
Prelude.Nothing
showEnum :: BaseCommand'Type -> String
showEnum BaseCommand'CONNECT = "CONNECT"
showEnum BaseCommand'CONNECTED = "CONNECTED"
showEnum BaseCommand'SUBSCRIBE = "SUBSCRIBE"
showEnum BaseCommand'PRODUCER = "PRODUCER"
showEnum BaseCommand'SEND = "SEND"
showEnum BaseCommand'SEND_RECEIPT = "SEND_RECEIPT"
showEnum BaseCommand'SEND_ERROR = "SEND_ERROR"
showEnum BaseCommand'MESSAGE = "MESSAGE"
showEnum BaseCommand'ACK = "ACK"
showEnum BaseCommand'FLOW = "FLOW"
showEnum BaseCommand'UNSUBSCRIBE = "UNSUBSCRIBE"
showEnum BaseCommand'SUCCESS = "SUCCESS"
showEnum BaseCommand'ERROR = "ERROR"
showEnum BaseCommand'CLOSE_PRODUCER = "CLOSE_PRODUCER"
showEnum BaseCommand'CLOSE_CONSUMER = "CLOSE_CONSUMER"
showEnum BaseCommand'PRODUCER_SUCCESS = "PRODUCER_SUCCESS"
showEnum BaseCommand'PING = "PING"
showEnum BaseCommand'PONG = "PONG"
showEnum BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
= "REDELIVER_UNACKNOWLEDGED_MESSAGES"
showEnum BaseCommand'PARTITIONED_METADATA = "PARTITIONED_METADATA"
showEnum BaseCommand'PARTITIONED_METADATA_RESPONSE
= "PARTITIONED_METADATA_RESPONSE"
showEnum BaseCommand'LOOKUP = "LOOKUP"
showEnum BaseCommand'LOOKUP_RESPONSE = "LOOKUP_RESPONSE"
showEnum BaseCommand'CONSUMER_STATS = "CONSUMER_STATS"
showEnum BaseCommand'CONSUMER_STATS_RESPONSE
= "CONSUMER_STATS_RESPONSE"
showEnum BaseCommand'REACHED_END_OF_TOPIC = "REACHED_END_OF_TOPIC"
showEnum BaseCommand'SEEK = "SEEK"
showEnum BaseCommand'GET_LAST_MESSAGE_ID = "GET_LAST_MESSAGE_ID"
showEnum BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
= "GET_LAST_MESSAGE_ID_RESPONSE"
showEnum BaseCommand'ACTIVE_CONSUMER_CHANGE
= "ACTIVE_CONSUMER_CHANGE"
showEnum BaseCommand'GET_TOPICS_OF_NAMESPACE
= "GET_TOPICS_OF_NAMESPACE"
showEnum BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
= "GET_TOPICS_OF_NAMESPACE_RESPONSE"
showEnum BaseCommand'GET_SCHEMA = "GET_SCHEMA"
showEnum BaseCommand'GET_SCHEMA_RESPONSE = "GET_SCHEMA_RESPONSE"
showEnum BaseCommand'AUTH_CHALLENGE = "AUTH_CHALLENGE"
showEnum BaseCommand'AUTH_RESPONSE = "AUTH_RESPONSE"
showEnum BaseCommand'ACK_RESPONSE = "ACK_RESPONSE"
showEnum BaseCommand'GET_OR_CREATE_SCHEMA = "GET_OR_CREATE_SCHEMA"
showEnum BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
= "GET_OR_CREATE_SCHEMA_RESPONSE"
showEnum BaseCommand'NEW_TXN = "NEW_TXN"
showEnum BaseCommand'NEW_TXN_RESPONSE = "NEW_TXN_RESPONSE"
showEnum BaseCommand'ADD_PARTITION_TO_TXN = "ADD_PARTITION_TO_TXN"
showEnum BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
= "ADD_PARTITION_TO_TXN_RESPONSE"
showEnum BaseCommand'ADD_SUBSCRIPTION_TO_TXN
= "ADD_SUBSCRIPTION_TO_TXN"
showEnum BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
= "ADD_SUBSCRIPTION_TO_TXN_RESPONSE"
showEnum BaseCommand'END_TXN = "END_TXN"
showEnum BaseCommand'END_TXN_RESPONSE = "END_TXN_RESPONSE"
showEnum BaseCommand'END_TXN_ON_PARTITION = "END_TXN_ON_PARTITION"
showEnum BaseCommand'END_TXN_ON_PARTITION_RESPONSE
= "END_TXN_ON_PARTITION_RESPONSE"
showEnum BaseCommand'END_TXN_ON_SUBSCRIPTION
= "END_TXN_ON_SUBSCRIPTION"
showEnum BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
= "END_TXN_ON_SUBSCRIPTION_RESPONSE"
readEnum :: String -> Maybe BaseCommand'Type
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CONNECT" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONNECT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CONNECTED" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONNECTED
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SUBSCRIBE" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SUBSCRIBE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PRODUCER" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PRODUCER
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SEND" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SEND_RECEIPT"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND_RECEIPT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SEND_ERROR" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEND_ERROR
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "MESSAGE" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'MESSAGE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ACK" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACK
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "FLOW" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'FLOW
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "UNSUBSCRIBE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'UNSUBSCRIBE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SUCCESS" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SUCCESS
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ERROR" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ERROR
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CLOSE_PRODUCER"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CLOSE_PRODUCER
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CLOSE_CONSUMER"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CLOSE_CONSUMER
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PRODUCER_SUCCESS"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PRODUCER_SUCCESS
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PING" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PING
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PONG" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PONG
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "REDELIVER_UNACKNOWLEDGED_MESSAGES"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PARTITIONED_METADATA"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PARTITIONED_METADATA
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PARTITIONED_METADATA_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'PARTITIONED_METADATA_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "LOOKUP" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'LOOKUP
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "LOOKUP_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'LOOKUP_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CONSUMER_STATS"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONSUMER_STATS
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "CONSUMER_STATS_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'CONSUMER_STATS_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "REACHED_END_OF_TOPIC"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'REACHED_END_OF_TOPIC
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SEEK" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'SEEK
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_LAST_MESSAGE_ID"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_LAST_MESSAGE_ID_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ACTIVE_CONSUMER_CHANGE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACTIVE_CONSUMER_CHANGE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_TOPICS_OF_NAMESPACE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_TOPICS_OF_NAMESPACE_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_SCHEMA" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_SCHEMA
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_SCHEMA_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_SCHEMA_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AUTH_CHALLENGE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'AUTH_CHALLENGE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AUTH_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'AUTH_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ACK_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ACK_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_OR_CREATE_SCHEMA"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "GET_OR_CREATE_SCHEMA_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "NEW_TXN" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'NEW_TXN
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "NEW_TXN_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'NEW_TXN_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ADD_PARTITION_TO_TXN"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ADD_PARTITION_TO_TXN_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ADD_SUBSCRIPTION_TO_TXN"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ADD_SUBSCRIPTION_TO_TXN_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN" = BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN_ON_PARTITION"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN_ON_PARTITION_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION_RESPONSE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN_ON_SUBSCRIPTION"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "END_TXN_ON_SUBSCRIPTION_RESPONSE"
= BaseCommand'Type -> Maybe BaseCommand'Type
forall a. a -> Maybe a
Prelude.Just BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe BaseCommand'Type) -> Maybe BaseCommand'Type
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe BaseCommand'Type
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded BaseCommand'Type where
minBound :: BaseCommand'Type
minBound = BaseCommand'Type
BaseCommand'CONNECT
maxBound :: BaseCommand'Type
maxBound = BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
instance Prelude.Enum BaseCommand'Type where
toEnum :: Int -> BaseCommand'Type
toEnum k__ :: Int
k__
= BaseCommand'Type
-> (BaseCommand'Type -> BaseCommand'Type)
-> Maybe BaseCommand'Type
-> BaseCommand'Type
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> BaseCommand'Type
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum Type: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
BaseCommand'Type -> BaseCommand'Type
forall a. a -> a
Prelude.id
(Int -> Maybe BaseCommand'Type
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: BaseCommand'Type -> Int
fromEnum BaseCommand'CONNECT = 2
fromEnum BaseCommand'CONNECTED = 3
fromEnum BaseCommand'SUBSCRIBE = 4
fromEnum BaseCommand'PRODUCER = 5
fromEnum BaseCommand'SEND = 6
fromEnum BaseCommand'SEND_RECEIPT = 7
fromEnum BaseCommand'SEND_ERROR = 8
fromEnum BaseCommand'MESSAGE = 9
fromEnum BaseCommand'ACK = 10
fromEnum BaseCommand'FLOW = 11
fromEnum BaseCommand'UNSUBSCRIBE = 12
fromEnum BaseCommand'SUCCESS = 13
fromEnum BaseCommand'ERROR = 14
fromEnum BaseCommand'CLOSE_PRODUCER = 15
fromEnum BaseCommand'CLOSE_CONSUMER = 16
fromEnum BaseCommand'PRODUCER_SUCCESS = 17
fromEnum BaseCommand'PING = 18
fromEnum BaseCommand'PONG = 19
fromEnum BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES = 20
fromEnum BaseCommand'PARTITIONED_METADATA = 21
fromEnum BaseCommand'PARTITIONED_METADATA_RESPONSE = 22
fromEnum BaseCommand'LOOKUP = 23
fromEnum BaseCommand'LOOKUP_RESPONSE = 24
fromEnum BaseCommand'CONSUMER_STATS = 25
fromEnum BaseCommand'CONSUMER_STATS_RESPONSE = 26
fromEnum BaseCommand'REACHED_END_OF_TOPIC = 27
fromEnum BaseCommand'SEEK = 28
fromEnum BaseCommand'GET_LAST_MESSAGE_ID = 29
fromEnum BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE = 30
fromEnum BaseCommand'ACTIVE_CONSUMER_CHANGE = 31
fromEnum BaseCommand'GET_TOPICS_OF_NAMESPACE = 32
fromEnum BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE = 33
fromEnum BaseCommand'GET_SCHEMA = 34
fromEnum BaseCommand'GET_SCHEMA_RESPONSE = 35
fromEnum BaseCommand'AUTH_CHALLENGE = 36
fromEnum BaseCommand'AUTH_RESPONSE = 37
fromEnum BaseCommand'ACK_RESPONSE = 38
fromEnum BaseCommand'GET_OR_CREATE_SCHEMA = 39
fromEnum BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE = 40
fromEnum BaseCommand'NEW_TXN = 50
fromEnum BaseCommand'NEW_TXN_RESPONSE = 51
fromEnum BaseCommand'ADD_PARTITION_TO_TXN = 52
fromEnum BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE = 53
fromEnum BaseCommand'ADD_SUBSCRIPTION_TO_TXN = 54
fromEnum BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE = 55
fromEnum BaseCommand'END_TXN = 56
fromEnum BaseCommand'END_TXN_RESPONSE = 57
fromEnum BaseCommand'END_TXN_ON_PARTITION = 58
fromEnum BaseCommand'END_TXN_ON_PARTITION_RESPONSE = 59
fromEnum BaseCommand'END_TXN_ON_SUBSCRIPTION = 60
fromEnum BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE = 61
succ :: BaseCommand'Type -> BaseCommand'Type
succ BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
= String -> BaseCommand'Type
forall a. HasCallStack => String -> a
Prelude.error
"BaseCommand'Type.succ: bad argument BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE. This value would be out of bounds."
succ BaseCommand'CONNECT = BaseCommand'Type
BaseCommand'CONNECTED
succ BaseCommand'CONNECTED = BaseCommand'Type
BaseCommand'SUBSCRIBE
succ BaseCommand'SUBSCRIBE = BaseCommand'Type
BaseCommand'PRODUCER
succ BaseCommand'PRODUCER = BaseCommand'Type
BaseCommand'SEND
succ BaseCommand'SEND = BaseCommand'Type
BaseCommand'SEND_RECEIPT
succ BaseCommand'SEND_RECEIPT = BaseCommand'Type
BaseCommand'SEND_ERROR
succ BaseCommand'SEND_ERROR = BaseCommand'Type
BaseCommand'MESSAGE
succ BaseCommand'MESSAGE = BaseCommand'Type
BaseCommand'ACK
succ BaseCommand'ACK = BaseCommand'Type
BaseCommand'FLOW
succ BaseCommand'FLOW = BaseCommand'Type
BaseCommand'UNSUBSCRIBE
succ BaseCommand'UNSUBSCRIBE = BaseCommand'Type
BaseCommand'SUCCESS
succ BaseCommand'SUCCESS = BaseCommand'Type
BaseCommand'ERROR
succ BaseCommand'ERROR = BaseCommand'Type
BaseCommand'CLOSE_PRODUCER
succ BaseCommand'CLOSE_PRODUCER = BaseCommand'Type
BaseCommand'CLOSE_CONSUMER
succ BaseCommand'CLOSE_CONSUMER = BaseCommand'Type
BaseCommand'PRODUCER_SUCCESS
succ BaseCommand'PRODUCER_SUCCESS = BaseCommand'Type
BaseCommand'PING
succ BaseCommand'PING = BaseCommand'Type
BaseCommand'PONG
succ BaseCommand'PONG
= BaseCommand'Type
BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
succ BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
= BaseCommand'Type
BaseCommand'PARTITIONED_METADATA
succ BaseCommand'PARTITIONED_METADATA
= BaseCommand'Type
BaseCommand'PARTITIONED_METADATA_RESPONSE
succ BaseCommand'PARTITIONED_METADATA_RESPONSE = BaseCommand'Type
BaseCommand'LOOKUP
succ BaseCommand'LOOKUP = BaseCommand'Type
BaseCommand'LOOKUP_RESPONSE
succ BaseCommand'LOOKUP_RESPONSE = BaseCommand'Type
BaseCommand'CONSUMER_STATS
succ BaseCommand'CONSUMER_STATS
= BaseCommand'Type
BaseCommand'CONSUMER_STATS_RESPONSE
succ BaseCommand'CONSUMER_STATS_RESPONSE
= BaseCommand'Type
BaseCommand'REACHED_END_OF_TOPIC
succ BaseCommand'REACHED_END_OF_TOPIC = BaseCommand'Type
BaseCommand'SEEK
succ BaseCommand'SEEK = BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID
succ BaseCommand'GET_LAST_MESSAGE_ID
= BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
succ BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
= BaseCommand'Type
BaseCommand'ACTIVE_CONSUMER_CHANGE
succ BaseCommand'ACTIVE_CONSUMER_CHANGE
= BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE
succ BaseCommand'GET_TOPICS_OF_NAMESPACE
= BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
succ BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
= BaseCommand'Type
BaseCommand'GET_SCHEMA
succ BaseCommand'GET_SCHEMA = BaseCommand'Type
BaseCommand'GET_SCHEMA_RESPONSE
succ BaseCommand'GET_SCHEMA_RESPONSE = BaseCommand'Type
BaseCommand'AUTH_CHALLENGE
succ BaseCommand'AUTH_CHALLENGE = BaseCommand'Type
BaseCommand'AUTH_RESPONSE
succ BaseCommand'AUTH_RESPONSE = BaseCommand'Type
BaseCommand'ACK_RESPONSE
succ BaseCommand'ACK_RESPONSE = BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA
succ BaseCommand'GET_OR_CREATE_SCHEMA
= BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
succ BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
= BaseCommand'Type
BaseCommand'NEW_TXN
succ BaseCommand'NEW_TXN = BaseCommand'Type
BaseCommand'NEW_TXN_RESPONSE
succ BaseCommand'NEW_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN
succ BaseCommand'ADD_PARTITION_TO_TXN
= BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
succ BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN
succ BaseCommand'ADD_SUBSCRIPTION_TO_TXN
= BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
succ BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'END_TXN
succ BaseCommand'END_TXN = BaseCommand'Type
BaseCommand'END_TXN_RESPONSE
succ BaseCommand'END_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION
succ BaseCommand'END_TXN_ON_PARTITION
= BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION_RESPONSE
succ BaseCommand'END_TXN_ON_PARTITION_RESPONSE
= BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION
succ BaseCommand'END_TXN_ON_SUBSCRIPTION
= BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
pred :: BaseCommand'Type -> BaseCommand'Type
pred BaseCommand'CONNECT
= String -> BaseCommand'Type
forall a. HasCallStack => String -> a
Prelude.error
"BaseCommand'Type.pred: bad argument BaseCommand'CONNECT. This value would be out of bounds."
pred BaseCommand'CONNECTED = BaseCommand'Type
BaseCommand'CONNECT
pred BaseCommand'SUBSCRIBE = BaseCommand'Type
BaseCommand'CONNECTED
pred BaseCommand'PRODUCER = BaseCommand'Type
BaseCommand'SUBSCRIBE
pred BaseCommand'SEND = BaseCommand'Type
BaseCommand'PRODUCER
pred BaseCommand'SEND_RECEIPT = BaseCommand'Type
BaseCommand'SEND
pred BaseCommand'SEND_ERROR = BaseCommand'Type
BaseCommand'SEND_RECEIPT
pred BaseCommand'MESSAGE = BaseCommand'Type
BaseCommand'SEND_ERROR
pred BaseCommand'ACK = BaseCommand'Type
BaseCommand'MESSAGE
pred BaseCommand'FLOW = BaseCommand'Type
BaseCommand'ACK
pred BaseCommand'UNSUBSCRIBE = BaseCommand'Type
BaseCommand'FLOW
pred BaseCommand'SUCCESS = BaseCommand'Type
BaseCommand'UNSUBSCRIBE
pred BaseCommand'ERROR = BaseCommand'Type
BaseCommand'SUCCESS
pred BaseCommand'CLOSE_PRODUCER = BaseCommand'Type
BaseCommand'ERROR
pred BaseCommand'CLOSE_CONSUMER = BaseCommand'Type
BaseCommand'CLOSE_PRODUCER
pred BaseCommand'PRODUCER_SUCCESS = BaseCommand'Type
BaseCommand'CLOSE_CONSUMER
pred BaseCommand'PING = BaseCommand'Type
BaseCommand'PRODUCER_SUCCESS
pred BaseCommand'PONG = BaseCommand'Type
BaseCommand'PING
pred BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
= BaseCommand'Type
BaseCommand'PONG
pred BaseCommand'PARTITIONED_METADATA
= BaseCommand'Type
BaseCommand'REDELIVER_UNACKNOWLEDGED_MESSAGES
pred BaseCommand'PARTITIONED_METADATA_RESPONSE
= BaseCommand'Type
BaseCommand'PARTITIONED_METADATA
pred BaseCommand'LOOKUP = BaseCommand'Type
BaseCommand'PARTITIONED_METADATA_RESPONSE
pred BaseCommand'LOOKUP_RESPONSE = BaseCommand'Type
BaseCommand'LOOKUP
pred BaseCommand'CONSUMER_STATS = BaseCommand'Type
BaseCommand'LOOKUP_RESPONSE
pred BaseCommand'CONSUMER_STATS_RESPONSE
= BaseCommand'Type
BaseCommand'CONSUMER_STATS
pred BaseCommand'REACHED_END_OF_TOPIC
= BaseCommand'Type
BaseCommand'CONSUMER_STATS_RESPONSE
pred BaseCommand'SEEK = BaseCommand'Type
BaseCommand'REACHED_END_OF_TOPIC
pred BaseCommand'GET_LAST_MESSAGE_ID = BaseCommand'Type
BaseCommand'SEEK
pred BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
= BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID
pred BaseCommand'ACTIVE_CONSUMER_CHANGE
= BaseCommand'Type
BaseCommand'GET_LAST_MESSAGE_ID_RESPONSE
pred BaseCommand'GET_TOPICS_OF_NAMESPACE
= BaseCommand'Type
BaseCommand'ACTIVE_CONSUMER_CHANGE
pred BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
= BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE
pred BaseCommand'GET_SCHEMA
= BaseCommand'Type
BaseCommand'GET_TOPICS_OF_NAMESPACE_RESPONSE
pred BaseCommand'GET_SCHEMA_RESPONSE = BaseCommand'Type
BaseCommand'GET_SCHEMA
pred BaseCommand'AUTH_CHALLENGE = BaseCommand'Type
BaseCommand'GET_SCHEMA_RESPONSE
pred BaseCommand'AUTH_RESPONSE = BaseCommand'Type
BaseCommand'AUTH_CHALLENGE
pred BaseCommand'ACK_RESPONSE = BaseCommand'Type
BaseCommand'AUTH_RESPONSE
pred BaseCommand'GET_OR_CREATE_SCHEMA = BaseCommand'Type
BaseCommand'ACK_RESPONSE
pred BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
= BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA
pred BaseCommand'NEW_TXN
= BaseCommand'Type
BaseCommand'GET_OR_CREATE_SCHEMA_RESPONSE
pred BaseCommand'NEW_TXN_RESPONSE = BaseCommand'Type
BaseCommand'NEW_TXN
pred BaseCommand'ADD_PARTITION_TO_TXN
= BaseCommand'Type
BaseCommand'NEW_TXN_RESPONSE
pred BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN
pred BaseCommand'ADD_SUBSCRIPTION_TO_TXN
= BaseCommand'Type
BaseCommand'ADD_PARTITION_TO_TXN_RESPONSE
pred BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
= BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN
pred BaseCommand'END_TXN
= BaseCommand'Type
BaseCommand'ADD_SUBSCRIPTION_TO_TXN_RESPONSE
pred BaseCommand'END_TXN_RESPONSE = BaseCommand'Type
BaseCommand'END_TXN
pred BaseCommand'END_TXN_ON_PARTITION
= BaseCommand'Type
BaseCommand'END_TXN_RESPONSE
pred BaseCommand'END_TXN_ON_PARTITION_RESPONSE
= BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION
pred BaseCommand'END_TXN_ON_SUBSCRIPTION
= BaseCommand'Type
BaseCommand'END_TXN_ON_PARTITION_RESPONSE
pred BaseCommand'END_TXN_ON_SUBSCRIPTION_RESPONSE
= BaseCommand'Type
BaseCommand'END_TXN_ON_SUBSCRIPTION
enumFrom :: BaseCommand'Type -> [BaseCommand'Type]
enumFrom = BaseCommand'Type -> [BaseCommand'Type]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
enumFromTo = BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
enumFromThen = BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: BaseCommand'Type
-> BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
enumFromThenTo = BaseCommand'Type
-> BaseCommand'Type -> BaseCommand'Type -> [BaseCommand'Type]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault BaseCommand'Type where
fieldDefault :: BaseCommand'Type
fieldDefault = BaseCommand'Type
BaseCommand'CONNECT
instance Control.DeepSeq.NFData BaseCommand'Type where
rnf :: BaseCommand'Type -> ()
rnf x__ :: BaseCommand'Type
x__ = BaseCommand'Type -> () -> ()
forall a b. a -> b -> b
Prelude.seq BaseCommand'Type
x__ ()
data CommandAck
= CommandAck'_constructor {CommandAck -> Word64
_CommandAck'consumerId :: !Data.Word.Word64,
CommandAck -> CommandAck'AckType
_CommandAck'ackType :: !CommandAck'AckType,
CommandAck -> Vector MessageIdData
_CommandAck'messageId :: !(Data.Vector.Vector MessageIdData),
CommandAck -> Maybe CommandAck'ValidationError
_CommandAck'validationError :: !(Prelude.Maybe CommandAck'ValidationError),
CommandAck -> Vector KeyLongValue
_CommandAck'properties :: !(Data.Vector.Vector KeyLongValue),
CommandAck -> Maybe Word64
_CommandAck'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAck -> Maybe Word64
_CommandAck'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAck -> FieldSet
_CommandAck'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAck -> CommandAck -> Bool
(CommandAck -> CommandAck -> Bool)
-> (CommandAck -> CommandAck -> Bool) -> Eq CommandAck
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAck -> CommandAck -> Bool
$c/= :: CommandAck -> CommandAck -> Bool
== :: CommandAck -> CommandAck -> Bool
$c== :: CommandAck -> CommandAck -> Bool
Prelude.Eq, Eq CommandAck
Eq CommandAck =>
(CommandAck -> CommandAck -> Ordering)
-> (CommandAck -> CommandAck -> Bool)
-> (CommandAck -> CommandAck -> Bool)
-> (CommandAck -> CommandAck -> Bool)
-> (CommandAck -> CommandAck -> Bool)
-> (CommandAck -> CommandAck -> CommandAck)
-> (CommandAck -> CommandAck -> CommandAck)
-> Ord CommandAck
CommandAck -> CommandAck -> Bool
CommandAck -> CommandAck -> Ordering
CommandAck -> CommandAck -> CommandAck
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAck -> CommandAck -> CommandAck
$cmin :: CommandAck -> CommandAck -> CommandAck
max :: CommandAck -> CommandAck -> CommandAck
$cmax :: CommandAck -> CommandAck -> CommandAck
>= :: CommandAck -> CommandAck -> Bool
$c>= :: CommandAck -> CommandAck -> Bool
> :: CommandAck -> CommandAck -> Bool
$c> :: CommandAck -> CommandAck -> Bool
<= :: CommandAck -> CommandAck -> Bool
$c<= :: CommandAck -> CommandAck -> Bool
< :: CommandAck -> CommandAck -> Bool
$c< :: CommandAck -> CommandAck -> Bool
compare :: CommandAck -> CommandAck -> Ordering
$ccompare :: CommandAck -> CommandAck -> Ordering
$cp1Ord :: Eq CommandAck
Prelude.Ord)
instance Prelude.Show CommandAck where
showsPrec :: Int -> CommandAck -> ShowS
showsPrec _ __x :: CommandAck
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAck -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAck
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAck "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64) -> CommandAck -> f CommandAck
fieldOf _
= ((Word64 -> f Word64) -> CommandAck -> f CommandAck)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Word64)
-> (CommandAck -> Word64 -> CommandAck)
-> Lens CommandAck CommandAck Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Word64
_CommandAck'consumerId
(\ x__ :: CommandAck
x__ y__ :: Word64
y__ -> CommandAck
x__ {_CommandAck'consumerId :: Word64
_CommandAck'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "ackType" CommandAck'AckType where
fieldOf :: Proxy# "ackType"
-> (CommandAck'AckType -> f CommandAck'AckType)
-> CommandAck
-> f CommandAck
fieldOf _
= ((CommandAck'AckType -> f CommandAck'AckType)
-> CommandAck -> f CommandAck)
-> ((CommandAck'AckType -> f CommandAck'AckType)
-> CommandAck'AckType -> f CommandAck'AckType)
-> (CommandAck'AckType -> f CommandAck'AckType)
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> CommandAck'AckType)
-> (CommandAck -> CommandAck'AckType -> CommandAck)
-> Lens CommandAck CommandAck CommandAck'AckType CommandAck'AckType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> CommandAck'AckType
_CommandAck'ackType (\ x__ :: CommandAck
x__ y__ :: CommandAck'AckType
y__ -> CommandAck
x__ {_CommandAck'ackType :: CommandAck'AckType
_CommandAck'ackType = CommandAck'AckType
y__}))
(CommandAck'AckType -> f CommandAck'AckType)
-> CommandAck'AckType -> f CommandAck'AckType
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "messageId" [MessageIdData] where
fieldOf :: Proxy# "messageId"
-> ([MessageIdData] -> f [MessageIdData])
-> CommandAck
-> f CommandAck
fieldOf _
= ((Vector MessageIdData -> f (Vector MessageIdData))
-> CommandAck -> f CommandAck)
-> (([MessageIdData] -> f [MessageIdData])
-> Vector MessageIdData -> f (Vector MessageIdData))
-> ([MessageIdData] -> f [MessageIdData])
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Vector MessageIdData)
-> (CommandAck -> Vector MessageIdData -> CommandAck)
-> Lens
CommandAck CommandAck (Vector MessageIdData) (Vector MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Vector MessageIdData
_CommandAck'messageId
(\ x__ :: CommandAck
x__ y__ :: Vector MessageIdData
y__ -> CommandAck
x__ {_CommandAck'messageId :: Vector MessageIdData
_CommandAck'messageId = Vector MessageIdData
y__}))
((Vector MessageIdData -> [MessageIdData])
-> (Vector MessageIdData
-> [MessageIdData] -> Vector MessageIdData)
-> Lens
(Vector MessageIdData)
(Vector MessageIdData)
[MessageIdData]
[MessageIdData]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector MessageIdData -> [MessageIdData]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [MessageIdData]
y__ -> [MessageIdData] -> Vector MessageIdData
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [MessageIdData]
y__))
instance Data.ProtoLens.Field.HasField CommandAck "vec'messageId" (Data.Vector.Vector MessageIdData) where
fieldOf :: Proxy# "vec'messageId"
-> (Vector MessageIdData -> f (Vector MessageIdData))
-> CommandAck
-> f CommandAck
fieldOf _
= ((Vector MessageIdData -> f (Vector MessageIdData))
-> CommandAck -> f CommandAck)
-> ((Vector MessageIdData -> f (Vector MessageIdData))
-> Vector MessageIdData -> f (Vector MessageIdData))
-> (Vector MessageIdData -> f (Vector MessageIdData))
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Vector MessageIdData)
-> (CommandAck -> Vector MessageIdData -> CommandAck)
-> Lens
CommandAck CommandAck (Vector MessageIdData) (Vector MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Vector MessageIdData
_CommandAck'messageId
(\ x__ :: CommandAck
x__ y__ :: Vector MessageIdData
y__ -> CommandAck
x__ {_CommandAck'messageId :: Vector MessageIdData
_CommandAck'messageId = Vector MessageIdData
y__}))
(Vector MessageIdData -> f (Vector MessageIdData))
-> Vector MessageIdData -> f (Vector MessageIdData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "validationError" CommandAck'ValidationError where
fieldOf :: Proxy# "validationError"
-> (CommandAck'ValidationError -> f CommandAck'ValidationError)
-> CommandAck
-> f CommandAck
fieldOf _
= ((Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> CommandAck -> f CommandAck)
-> ((CommandAck'ValidationError -> f CommandAck'ValidationError)
-> Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> (CommandAck'ValidationError -> f CommandAck'ValidationError)
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe CommandAck'ValidationError)
-> (CommandAck -> Maybe CommandAck'ValidationError -> CommandAck)
-> Lens
CommandAck
CommandAck
(Maybe CommandAck'ValidationError)
(Maybe CommandAck'ValidationError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe CommandAck'ValidationError
_CommandAck'validationError
(\ x__ :: CommandAck
x__ y__ :: Maybe CommandAck'ValidationError
y__ -> CommandAck
x__ {_CommandAck'validationError :: Maybe CommandAck'ValidationError
_CommandAck'validationError = Maybe CommandAck'ValidationError
y__}))
(CommandAck'ValidationError
-> Lens'
(Maybe CommandAck'ValidationError) CommandAck'ValidationError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandAck'ValidationError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAck "maybe'validationError" (Prelude.Maybe CommandAck'ValidationError) where
fieldOf :: Proxy# "maybe'validationError"
-> (Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> CommandAck
-> f CommandAck
fieldOf _
= ((Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> CommandAck -> f CommandAck)
-> ((Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> (Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe CommandAck'ValidationError)
-> (CommandAck -> Maybe CommandAck'ValidationError -> CommandAck)
-> Lens
CommandAck
CommandAck
(Maybe CommandAck'ValidationError)
(Maybe CommandAck'ValidationError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe CommandAck'ValidationError
_CommandAck'validationError
(\ x__ :: CommandAck
x__ y__ :: Maybe CommandAck'ValidationError
y__ -> CommandAck
x__ {_CommandAck'validationError :: Maybe CommandAck'ValidationError
_CommandAck'validationError = Maybe CommandAck'ValidationError
y__}))
(Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError))
-> Maybe CommandAck'ValidationError
-> f (Maybe CommandAck'ValidationError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "properties" [KeyLongValue] where
fieldOf :: Proxy# "properties"
-> ([KeyLongValue] -> f [KeyLongValue])
-> CommandAck
-> f CommandAck
fieldOf _
= ((Vector KeyLongValue -> f (Vector KeyLongValue))
-> CommandAck -> f CommandAck)
-> (([KeyLongValue] -> f [KeyLongValue])
-> Vector KeyLongValue -> f (Vector KeyLongValue))
-> ([KeyLongValue] -> f [KeyLongValue])
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Vector KeyLongValue)
-> (CommandAck -> Vector KeyLongValue -> CommandAck)
-> Lens
CommandAck CommandAck (Vector KeyLongValue) (Vector KeyLongValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Vector KeyLongValue
_CommandAck'properties
(\ x__ :: CommandAck
x__ y__ :: Vector KeyLongValue
y__ -> CommandAck
x__ {_CommandAck'properties :: Vector KeyLongValue
_CommandAck'properties = Vector KeyLongValue
y__}))
((Vector KeyLongValue -> [KeyLongValue])
-> (Vector KeyLongValue -> [KeyLongValue] -> Vector KeyLongValue)
-> Lens
(Vector KeyLongValue)
(Vector KeyLongValue)
[KeyLongValue]
[KeyLongValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyLongValue -> [KeyLongValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyLongValue]
y__ -> [KeyLongValue] -> Vector KeyLongValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyLongValue]
y__))
instance Data.ProtoLens.Field.HasField CommandAck "vec'properties" (Data.Vector.Vector KeyLongValue) where
fieldOf :: Proxy# "vec'properties"
-> (Vector KeyLongValue -> f (Vector KeyLongValue))
-> CommandAck
-> f CommandAck
fieldOf _
= ((Vector KeyLongValue -> f (Vector KeyLongValue))
-> CommandAck -> f CommandAck)
-> ((Vector KeyLongValue -> f (Vector KeyLongValue))
-> Vector KeyLongValue -> f (Vector KeyLongValue))
-> (Vector KeyLongValue -> f (Vector KeyLongValue))
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Vector KeyLongValue)
-> (CommandAck -> Vector KeyLongValue -> CommandAck)
-> Lens
CommandAck CommandAck (Vector KeyLongValue) (Vector KeyLongValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Vector KeyLongValue
_CommandAck'properties
(\ x__ :: CommandAck
x__ y__ :: Vector KeyLongValue
y__ -> CommandAck
x__ {_CommandAck'properties :: Vector KeyLongValue
_CommandAck'properties = Vector KeyLongValue
y__}))
(Vector KeyLongValue -> f (Vector KeyLongValue))
-> Vector KeyLongValue -> f (Vector KeyLongValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64) -> CommandAck -> f CommandAck
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe Word64)
-> (CommandAck -> Maybe Word64 -> CommandAck)
-> Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe Word64
_CommandAck'txnidLeastBits
(\ x__ :: CommandAck
x__ y__ :: Maybe Word64
y__ -> CommandAck
x__ {_CommandAck'txnidLeastBits :: Maybe Word64
_CommandAck'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAck "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe Word64)
-> (CommandAck -> Maybe Word64 -> CommandAck)
-> Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe Word64
_CommandAck'txnidLeastBits
(\ x__ :: CommandAck
x__ y__ :: Maybe Word64
y__ -> CommandAck
x__ {_CommandAck'txnidLeastBits :: Maybe Word64
_CommandAck'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAck "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64) -> CommandAck -> f CommandAck
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe Word64)
-> (CommandAck -> Maybe Word64 -> CommandAck)
-> Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe Word64
_CommandAck'txnidMostBits
(\ x__ :: CommandAck
x__ y__ :: Maybe Word64
y__ -> CommandAck
x__ {_CommandAck'txnidMostBits :: Maybe Word64
_CommandAck'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAck "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64)) -> CommandAck -> f CommandAck)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAck
-> f CommandAck
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAck -> Maybe Word64)
-> (CommandAck -> Maybe Word64 -> CommandAck)
-> Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> Maybe Word64
_CommandAck'txnidMostBits
(\ x__ :: CommandAck
x__ y__ :: Maybe Word64
y__ -> CommandAck
x__ {_CommandAck'txnidMostBits :: Maybe Word64
_CommandAck'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAck where
messageName :: Proxy CommandAck -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandAck"
packedMessageDescriptor :: Proxy CommandAck -> ByteString
packedMessageDescriptor _
= "\n\
\\n\
\CommandAck\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2;\n\
\\back_type\CAN\STX \STX(\SO2 .pulsar.proto.CommandAck.AckTypeR\aackType\DC2:\n\
\\n\
\message_id\CAN\ETX \ETX(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC2S\n\
\\DLEvalidation_error\CAN\EOT \SOH(\SO2(.pulsar.proto.CommandAck.ValidationErrorR\SIvalidationError\DC2:\n\
\\n\
\properties\CAN\ENQ \ETX(\v2\SUB.pulsar.proto.KeyLongValueR\n\
\properties\DC2+\n\
\\DLEtxnid_least_bits\CAN\ACK \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\a \SOH(\EOT:\SOH0R\rtxnidMostBits\")\n\
\\aAckType\DC2\SO\n\
\\n\
\Individual\DLE\NUL\DC2\SO\n\
\\n\
\Cumulative\DLE\SOH\"\143\SOH\n\
\\SIValidationError\DC2\RS\n\
\\SUBUncompressedSizeCorruption\DLE\NUL\DC2\SYN\n\
\\DC2DecompressionError\DLE\SOH\DC2\DC4\n\
\\DLEChecksumMismatch\DLE\STX\DC2\EM\n\
\\NAKBatchDeSerializeError\DLE\ETX\DC2\DC3\n\
\\SIDecryptionError\DLE\EOT"
packedFileDescriptor :: Proxy CommandAck -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAck)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandAck
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAck Word64
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandAck CommandAck Word64 Word64
-> FieldAccessor CommandAck Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandAck
ackType__field_descriptor :: FieldDescriptor CommandAck
ackType__field_descriptor
= String
-> FieldTypeDescriptor CommandAck'AckType
-> FieldAccessor CommandAck CommandAck'AckType
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ack_type"
(ScalarField CommandAck'AckType
-> FieldTypeDescriptor CommandAck'AckType
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandAck'AckType
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandAck'AckType)
(WireDefault CommandAck'AckType
-> Lens CommandAck CommandAck CommandAck'AckType CommandAck'AckType
-> FieldAccessor CommandAck CommandAck'AckType
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault CommandAck'AckType
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "ackType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackType")) ::
Data.ProtoLens.FieldDescriptor CommandAck
messageId__field_descriptor :: FieldDescriptor CommandAck
messageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandAck MessageIdData
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(Packing
-> Lens' CommandAck [MessageIdData]
-> FieldAccessor CommandAck MessageIdData
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId")) ::
Data.ProtoLens.FieldDescriptor CommandAck
validationError__field_descriptor :: FieldDescriptor CommandAck
validationError__field_descriptor
= String
-> FieldTypeDescriptor CommandAck'ValidationError
-> FieldAccessor CommandAck CommandAck'ValidationError
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"validation_error"
(ScalarField CommandAck'ValidationError
-> FieldTypeDescriptor CommandAck'ValidationError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandAck'ValidationError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandAck'ValidationError)
(Lens
CommandAck
CommandAck
(Maybe CommandAck'ValidationError)
(Maybe CommandAck'ValidationError)
-> FieldAccessor CommandAck CommandAck'ValidationError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'validationError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'validationError")) ::
Data.ProtoLens.FieldDescriptor CommandAck
properties__field_descriptor :: FieldDescriptor CommandAck
properties__field_descriptor
= String
-> FieldTypeDescriptor KeyLongValue
-> FieldAccessor CommandAck KeyLongValue
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"properties"
(MessageOrGroup -> FieldTypeDescriptor KeyLongValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyLongValue)
(Packing
-> Lens' CommandAck [KeyLongValue]
-> FieldAccessor CommandAck KeyLongValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"properties")) ::
Data.ProtoLens.FieldDescriptor CommandAck
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAck
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAck Word64
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandAck Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAck
txnidMostBits__field_descriptor :: FieldDescriptor CommandAck
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAck Word64
-> FieldDescriptor CommandAck
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandAck CommandAck (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandAck Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAck
in
[(Tag, FieldDescriptor CommandAck)]
-> Map Tag (FieldDescriptor CommandAck)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAck
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAck
ackType__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAck
messageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAck
validationError__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandAck
properties__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandAck
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandAck
txnidMostBits__field_descriptor)]
unknownFields :: LensLike' f CommandAck FieldSet
unknownFields
= (CommandAck -> FieldSet)
-> (CommandAck -> FieldSet -> CommandAck)
-> Lens' CommandAck FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAck -> FieldSet
_CommandAck'_unknownFields
(\ x__ :: CommandAck
x__ y__ :: FieldSet
y__ -> CommandAck
x__ {_CommandAck'_unknownFields :: FieldSet
_CommandAck'_unknownFields = FieldSet
y__})
defMessage :: CommandAck
defMessage
= $WCommandAck'_constructor :: Word64
-> CommandAck'AckType
-> Vector MessageIdData
-> Maybe CommandAck'ValidationError
-> Vector KeyLongValue
-> Maybe Word64
-> Maybe Word64
-> FieldSet
-> CommandAck
CommandAck'_constructor
{_CommandAck'consumerId :: Word64
_CommandAck'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAck'ackType :: CommandAck'AckType
_CommandAck'ackType = CommandAck'AckType
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAck'messageId :: Vector MessageIdData
_CommandAck'messageId = Vector MessageIdData
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandAck'validationError :: Maybe CommandAck'ValidationError
_CommandAck'validationError = Maybe CommandAck'ValidationError
forall a. Maybe a
Prelude.Nothing,
_CommandAck'properties :: Vector KeyLongValue
_CommandAck'properties = Vector KeyLongValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandAck'txnidLeastBits :: Maybe Word64
_CommandAck'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAck'txnidMostBits :: Maybe Word64
_CommandAck'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAck'_unknownFields :: FieldSet
_CommandAck'_unknownFields = []}
parseMessage :: Parser CommandAck
parseMessage
= let
loop ::
CommandAck
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld MessageIdData
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyLongValue
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAck
loop :: CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
x :: CommandAck
x
required'ackType :: Bool
required'ackType
required'consumerId :: Bool
required'consumerId
mutable'messageId :: Growing Vector RealWorld MessageIdData
mutable'messageId
mutable'properties :: Growing Vector RealWorld KeyLongValue
mutable'properties
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector MessageIdData
frozen'messageId <- IO (Vector MessageIdData) -> Parser (Vector MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) MessageIdData
-> IO (Vector MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld MessageIdData
Growing Vector (PrimState IO) MessageIdData
mutable'messageId)
Vector KeyLongValue
frozen'properties <- IO (Vector KeyLongValue) -> Parser (Vector KeyLongValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyLongValue
-> IO (Vector KeyLongValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyLongValue
Growing Vector (PrimState IO) KeyLongValue
mutable'properties)
(let
missing :: [String]
missing
= (if Bool
required'ackType then (:) "ack_type" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAck -> Parser CommandAck
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandAck CommandAck FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAck CommandAck FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandAck CommandAck (Vector MessageIdData) (Vector MessageIdData)
-> Vector MessageIdData -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'messageId")
Vector MessageIdData
frozen'messageId
(Setter
CommandAck CommandAck (Vector KeyLongValue) (Vector KeyLongValue)
-> Vector KeyLongValue -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties")
Vector KeyLongValue
frozen'properties
CommandAck
x)))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter CommandAck CommandAck Word64 Word64
-> Word64 -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandAck
x)
Bool
required'ackType
Bool
Prelude.False
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
16
-> do CommandAck'AckType
y <- Parser CommandAck'AckType -> String -> Parser CommandAck'AckType
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandAck'AckType)
-> Parser Int -> Parser CommandAck'AckType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandAck'AckType
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"ack_type"
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter CommandAck CommandAck CommandAck'AckType CommandAck'AckType
-> CommandAck'AckType -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "ackType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackType") CommandAck'AckType
y CommandAck
x)
Bool
Prelude.False
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
26
-> do !MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message_id"
Growing Vector RealWorld MessageIdData
v <- IO (Growing Vector RealWorld MessageIdData)
-> Parser (Growing Vector RealWorld MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) MessageIdData
-> MessageIdData
-> IO (Growing Vector (PrimState IO) MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld MessageIdData
Growing Vector (PrimState IO) MessageIdData
mutable'messageId MessageIdData
y)
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop CommandAck
x Bool
required'ackType Bool
required'consumerId Growing Vector RealWorld MessageIdData
v Growing Vector RealWorld KeyLongValue
mutable'properties
32
-> do CommandAck'ValidationError
y <- Parser CommandAck'ValidationError
-> String -> Parser CommandAck'ValidationError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandAck'ValidationError)
-> Parser Int -> Parser CommandAck'ValidationError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandAck'ValidationError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"validation_error"
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter
CommandAck
CommandAck
CommandAck'ValidationError
CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "validationError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"validationError") CommandAck'ValidationError
y CommandAck
x)
Bool
required'ackType
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
42
-> do !KeyLongValue
y <- Parser KeyLongValue -> String -> Parser KeyLongValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyLongValue -> Parser KeyLongValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyLongValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"properties"
Growing Vector RealWorld KeyLongValue
v <- IO (Growing Vector RealWorld KeyLongValue)
-> Parser (Growing Vector RealWorld KeyLongValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyLongValue
-> KeyLongValue -> IO (Growing Vector (PrimState IO) KeyLongValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyLongValue
Growing Vector (PrimState IO) KeyLongValue
mutable'properties KeyLongValue
y)
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop CommandAck
x Bool
required'ackType Bool
required'consumerId Growing Vector RealWorld MessageIdData
mutable'messageId Growing Vector RealWorld KeyLongValue
v
48
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter CommandAck CommandAck Word64 Word64
-> Word64 -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAck
x)
Bool
required'ackType
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
56
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter CommandAck CommandAck Word64 Word64
-> Word64 -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAck
x)
Bool
required'ackType
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
(Setter CommandAck CommandAck FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandAck -> CommandAck
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAck CommandAck FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAck
x)
Bool
required'ackType
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties
in
Parser CommandAck -> String -> Parser CommandAck
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld MessageIdData
mutable'messageId <- IO (Growing Vector RealWorld MessageIdData)
-> Parser (Growing Vector RealWorld MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
Growing Vector RealWorld KeyLongValue
mutable'properties <- IO (Growing Vector RealWorld KeyLongValue)
-> Parser (Growing Vector RealWorld KeyLongValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyLongValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandAck
-> Bool
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Growing Vector RealWorld KeyLongValue
-> Parser CommandAck
loop
CommandAck
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld MessageIdData
mutable'messageId
Growing Vector RealWorld KeyLongValue
mutable'properties)
"CommandAck"
buildMessage :: CommandAck -> Builder
buildMessage
= \ _x :: CommandAck
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandAck CommandAck Word64 Word64
-> CommandAck -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandAck
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder)
-> (CommandAck'AckType -> Int) -> CommandAck'AckType -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandAck'AckType -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
CommandAck'AckType
CommandAck
CommandAck
CommandAck'AckType
CommandAck'AckType
-> CommandAck -> CommandAck'AckType
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "ackType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackType") CommandAck
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((MessageIdData -> Builder) -> Vector MessageIdData -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: MessageIdData
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
MessageIdData
_v))
(FoldLike
(Vector MessageIdData)
CommandAck
CommandAck
(Vector MessageIdData)
(Vector MessageIdData)
-> CommandAck -> Vector MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'messageId") CommandAck
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandAck'ValidationError)
CommandAck
CommandAck
(Maybe CommandAck'ValidationError)
(Maybe CommandAck'ValidationError)
-> CommandAck -> Maybe CommandAck'ValidationError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'validationError" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'validationError") CommandAck
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandAck'ValidationError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder)
-> (CommandAck'ValidationError -> Int)
-> CommandAck'ValidationError
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandAck'ValidationError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CommandAck'ValidationError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyLongValue -> Builder) -> Vector KeyLongValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyLongValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder)
-> (KeyLongValue -> ByteString) -> KeyLongValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyLongValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyLongValue
_v))
(FoldLike
(Vector KeyLongValue)
CommandAck
CommandAck
(Vector KeyLongValue)
(Vector KeyLongValue)
-> CommandAck -> Vector KeyLongValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties") CommandAck
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64) CommandAck CommandAck (Maybe Word64) (Maybe Word64)
-> CommandAck -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAck
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 48)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64) CommandAck CommandAck (Maybe Word64) (Maybe Word64)
-> CommandAck -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAck
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 56)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandAck CommandAck FieldSet FieldSet
-> CommandAck -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandAck CommandAck FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAck
_x))))))))
instance Control.DeepSeq.NFData CommandAck where
rnf :: CommandAck -> ()
rnf
= \ x__ :: CommandAck
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> FieldSet
_CommandAck'_unknownFields CommandAck
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> Word64
_CommandAck'consumerId CommandAck
x__)
(CommandAck'AckType -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> CommandAck'AckType
_CommandAck'ackType CommandAck
x__)
(Vector MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> Vector MessageIdData
_CommandAck'messageId CommandAck
x__)
(Maybe CommandAck'ValidationError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> Maybe CommandAck'ValidationError
_CommandAck'validationError CommandAck
x__)
(Vector KeyLongValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> Vector KeyLongValue
_CommandAck'properties CommandAck
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAck -> Maybe Word64
_CommandAck'txnidLeastBits CommandAck
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandAck -> Maybe Word64
_CommandAck'txnidMostBits CommandAck
x__) ())))))))
data CommandAck'AckType
= CommandAck'Individual | CommandAck'Cumulative
deriving stock (Int -> CommandAck'AckType -> ShowS
[CommandAck'AckType] -> ShowS
CommandAck'AckType -> String
(Int -> CommandAck'AckType -> ShowS)
-> (CommandAck'AckType -> String)
-> ([CommandAck'AckType] -> ShowS)
-> Show CommandAck'AckType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandAck'AckType] -> ShowS
$cshowList :: [CommandAck'AckType] -> ShowS
show :: CommandAck'AckType -> String
$cshow :: CommandAck'AckType -> String
showsPrec :: Int -> CommandAck'AckType -> ShowS
$cshowsPrec :: Int -> CommandAck'AckType -> ShowS
Prelude.Show, CommandAck'AckType -> CommandAck'AckType -> Bool
(CommandAck'AckType -> CommandAck'AckType -> Bool)
-> (CommandAck'AckType -> CommandAck'AckType -> Bool)
-> Eq CommandAck'AckType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c/= :: CommandAck'AckType -> CommandAck'AckType -> Bool
== :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c== :: CommandAck'AckType -> CommandAck'AckType -> Bool
Prelude.Eq, Eq CommandAck'AckType
Eq CommandAck'AckType =>
(CommandAck'AckType -> CommandAck'AckType -> Ordering)
-> (CommandAck'AckType -> CommandAck'AckType -> Bool)
-> (CommandAck'AckType -> CommandAck'AckType -> Bool)
-> (CommandAck'AckType -> CommandAck'AckType -> Bool)
-> (CommandAck'AckType -> CommandAck'AckType -> Bool)
-> (CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType)
-> (CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType)
-> Ord CommandAck'AckType
CommandAck'AckType -> CommandAck'AckType -> Bool
CommandAck'AckType -> CommandAck'AckType -> Ordering
CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType
$cmin :: CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType
max :: CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType
$cmax :: CommandAck'AckType -> CommandAck'AckType -> CommandAck'AckType
>= :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c>= :: CommandAck'AckType -> CommandAck'AckType -> Bool
> :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c> :: CommandAck'AckType -> CommandAck'AckType -> Bool
<= :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c<= :: CommandAck'AckType -> CommandAck'AckType -> Bool
< :: CommandAck'AckType -> CommandAck'AckType -> Bool
$c< :: CommandAck'AckType -> CommandAck'AckType -> Bool
compare :: CommandAck'AckType -> CommandAck'AckType -> Ordering
$ccompare :: CommandAck'AckType -> CommandAck'AckType -> Ordering
$cp1Ord :: Eq CommandAck'AckType
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandAck'AckType where
maybeToEnum :: Int -> Maybe CommandAck'AckType
maybeToEnum 0 = CommandAck'AckType -> Maybe CommandAck'AckType
forall a. a -> Maybe a
Prelude.Just CommandAck'AckType
CommandAck'Individual
maybeToEnum 1 = CommandAck'AckType -> Maybe CommandAck'AckType
forall a. a -> Maybe a
Prelude.Just CommandAck'AckType
CommandAck'Cumulative
maybeToEnum _ = Maybe CommandAck'AckType
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandAck'AckType -> String
showEnum CommandAck'Individual = "Individual"
showEnum CommandAck'Cumulative = "Cumulative"
readEnum :: String -> Maybe CommandAck'AckType
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Individual" = CommandAck'AckType -> Maybe CommandAck'AckType
forall a. a -> Maybe a
Prelude.Just CommandAck'AckType
CommandAck'Individual
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Cumulative" = CommandAck'AckType -> Maybe CommandAck'AckType
forall a. a -> Maybe a
Prelude.Just CommandAck'AckType
CommandAck'Cumulative
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandAck'AckType) -> Maybe CommandAck'AckType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandAck'AckType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandAck'AckType where
minBound :: CommandAck'AckType
minBound = CommandAck'AckType
CommandAck'Individual
maxBound :: CommandAck'AckType
maxBound = CommandAck'AckType
CommandAck'Cumulative
instance Prelude.Enum CommandAck'AckType where
toEnum :: Int -> CommandAck'AckType
toEnum k__ :: Int
k__
= CommandAck'AckType
-> (CommandAck'AckType -> CommandAck'AckType)
-> Maybe CommandAck'AckType
-> CommandAck'AckType
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandAck'AckType
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum AckType: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandAck'AckType -> CommandAck'AckType
forall a. a -> a
Prelude.id
(Int -> Maybe CommandAck'AckType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandAck'AckType -> Int
fromEnum CommandAck'Individual = 0
fromEnum CommandAck'Cumulative = 1
succ :: CommandAck'AckType -> CommandAck'AckType
succ CommandAck'Cumulative
= String -> CommandAck'AckType
forall a. HasCallStack => String -> a
Prelude.error
"CommandAck'AckType.succ: bad argument CommandAck'Cumulative. This value would be out of bounds."
succ CommandAck'Individual = CommandAck'AckType
CommandAck'Cumulative
pred :: CommandAck'AckType -> CommandAck'AckType
pred CommandAck'Individual
= String -> CommandAck'AckType
forall a. HasCallStack => String -> a
Prelude.error
"CommandAck'AckType.pred: bad argument CommandAck'Individual. This value would be out of bounds."
pred CommandAck'Cumulative = CommandAck'AckType
CommandAck'Individual
enumFrom :: CommandAck'AckType -> [CommandAck'AckType]
enumFrom = CommandAck'AckType -> [CommandAck'AckType]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
enumFromTo = CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
enumFromThen = CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandAck'AckType
-> CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
enumFromThenTo = CommandAck'AckType
-> CommandAck'AckType -> CommandAck'AckType -> [CommandAck'AckType]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandAck'AckType where
fieldDefault :: CommandAck'AckType
fieldDefault = CommandAck'AckType
CommandAck'Individual
instance Control.DeepSeq.NFData CommandAck'AckType where
rnf :: CommandAck'AckType -> ()
rnf x__ :: CommandAck'AckType
x__ = CommandAck'AckType -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandAck'AckType
x__ ()
data CommandAck'ValidationError
= CommandAck'UncompressedSizeCorruption |
CommandAck'DecompressionError |
CommandAck'ChecksumMismatch |
CommandAck'BatchDeSerializeError |
CommandAck'DecryptionError
deriving stock (Int -> CommandAck'ValidationError -> ShowS
[CommandAck'ValidationError] -> ShowS
CommandAck'ValidationError -> String
(Int -> CommandAck'ValidationError -> ShowS)
-> (CommandAck'ValidationError -> String)
-> ([CommandAck'ValidationError] -> ShowS)
-> Show CommandAck'ValidationError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandAck'ValidationError] -> ShowS
$cshowList :: [CommandAck'ValidationError] -> ShowS
show :: CommandAck'ValidationError -> String
$cshow :: CommandAck'ValidationError -> String
showsPrec :: Int -> CommandAck'ValidationError -> ShowS
$cshowsPrec :: Int -> CommandAck'ValidationError -> ShowS
Prelude.Show, CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
(CommandAck'ValidationError -> CommandAck'ValidationError -> Bool)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> Bool)
-> Eq CommandAck'ValidationError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c/= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
== :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c== :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
Prelude.Eq, Eq CommandAck'ValidationError
Eq CommandAck'ValidationError =>
(CommandAck'ValidationError
-> CommandAck'ValidationError -> Ordering)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> Bool)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> Bool)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> Bool)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> Bool)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError)
-> (CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError)
-> Ord CommandAck'ValidationError
CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
CommandAck'ValidationError
-> CommandAck'ValidationError -> Ordering
CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError
$cmin :: CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError
max :: CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError
$cmax :: CommandAck'ValidationError
-> CommandAck'ValidationError -> CommandAck'ValidationError
>= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c>= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
> :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c> :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
<= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c<= :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
< :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
$c< :: CommandAck'ValidationError -> CommandAck'ValidationError -> Bool
compare :: CommandAck'ValidationError
-> CommandAck'ValidationError -> Ordering
$ccompare :: CommandAck'ValidationError
-> CommandAck'ValidationError -> Ordering
$cp1Ord :: Eq CommandAck'ValidationError
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandAck'ValidationError where
maybeToEnum :: Int -> Maybe CommandAck'ValidationError
maybeToEnum 0 = CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'UncompressedSizeCorruption
maybeToEnum 1 = CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'DecompressionError
maybeToEnum 2 = CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'ChecksumMismatch
maybeToEnum 3 = CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'BatchDeSerializeError
maybeToEnum 4 = CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'DecryptionError
maybeToEnum _ = Maybe CommandAck'ValidationError
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandAck'ValidationError -> String
showEnum CommandAck'UncompressedSizeCorruption
= "UncompressedSizeCorruption"
showEnum CommandAck'DecompressionError = "DecompressionError"
showEnum CommandAck'ChecksumMismatch = "ChecksumMismatch"
showEnum CommandAck'BatchDeSerializeError = "BatchDeSerializeError"
showEnum CommandAck'DecryptionError = "DecryptionError"
readEnum :: String -> Maybe CommandAck'ValidationError
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "UncompressedSizeCorruption"
= CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'UncompressedSizeCorruption
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "DecompressionError"
= CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'DecompressionError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ChecksumMismatch"
= CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'ChecksumMismatch
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "BatchDeSerializeError"
= CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'BatchDeSerializeError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "DecryptionError"
= CommandAck'ValidationError -> Maybe CommandAck'ValidationError
forall a. a -> Maybe a
Prelude.Just CommandAck'ValidationError
CommandAck'DecryptionError
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandAck'ValidationError)
-> Maybe CommandAck'ValidationError
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandAck'ValidationError
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandAck'ValidationError where
minBound :: CommandAck'ValidationError
minBound = CommandAck'ValidationError
CommandAck'UncompressedSizeCorruption
maxBound :: CommandAck'ValidationError
maxBound = CommandAck'ValidationError
CommandAck'DecryptionError
instance Prelude.Enum CommandAck'ValidationError where
toEnum :: Int -> CommandAck'ValidationError
toEnum k__ :: Int
k__
= CommandAck'ValidationError
-> (CommandAck'ValidationError -> CommandAck'ValidationError)
-> Maybe CommandAck'ValidationError
-> CommandAck'ValidationError
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandAck'ValidationError
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum ValidationError: "
(Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandAck'ValidationError -> CommandAck'ValidationError
forall a. a -> a
Prelude.id
(Int -> Maybe CommandAck'ValidationError
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandAck'ValidationError -> Int
fromEnum CommandAck'UncompressedSizeCorruption = 0
fromEnum CommandAck'DecompressionError = 1
fromEnum CommandAck'ChecksumMismatch = 2
fromEnum CommandAck'BatchDeSerializeError = 3
fromEnum CommandAck'DecryptionError = 4
succ :: CommandAck'ValidationError -> CommandAck'ValidationError
succ CommandAck'DecryptionError
= String -> CommandAck'ValidationError
forall a. HasCallStack => String -> a
Prelude.error
"CommandAck'ValidationError.succ: bad argument CommandAck'DecryptionError. This value would be out of bounds."
succ CommandAck'UncompressedSizeCorruption
= CommandAck'ValidationError
CommandAck'DecompressionError
succ CommandAck'DecompressionError = CommandAck'ValidationError
CommandAck'ChecksumMismatch
succ CommandAck'ChecksumMismatch = CommandAck'ValidationError
CommandAck'BatchDeSerializeError
succ CommandAck'BatchDeSerializeError = CommandAck'ValidationError
CommandAck'DecryptionError
pred :: CommandAck'ValidationError -> CommandAck'ValidationError
pred CommandAck'UncompressedSizeCorruption
= String -> CommandAck'ValidationError
forall a. HasCallStack => String -> a
Prelude.error
"CommandAck'ValidationError.pred: bad argument CommandAck'UncompressedSizeCorruption. This value would be out of bounds."
pred CommandAck'DecompressionError
= CommandAck'ValidationError
CommandAck'UncompressedSizeCorruption
pred CommandAck'ChecksumMismatch = CommandAck'ValidationError
CommandAck'DecompressionError
pred CommandAck'BatchDeSerializeError = CommandAck'ValidationError
CommandAck'ChecksumMismatch
pred CommandAck'DecryptionError = CommandAck'ValidationError
CommandAck'BatchDeSerializeError
enumFrom :: CommandAck'ValidationError -> [CommandAck'ValidationError]
enumFrom = CommandAck'ValidationError -> [CommandAck'ValidationError]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandAck'ValidationError
-> CommandAck'ValidationError -> [CommandAck'ValidationError]
enumFromTo = CommandAck'ValidationError
-> CommandAck'ValidationError -> [CommandAck'ValidationError]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandAck'ValidationError
-> CommandAck'ValidationError -> [CommandAck'ValidationError]
enumFromThen = CommandAck'ValidationError
-> CommandAck'ValidationError -> [CommandAck'ValidationError]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandAck'ValidationError
-> CommandAck'ValidationError
-> CommandAck'ValidationError
-> [CommandAck'ValidationError]
enumFromThenTo = CommandAck'ValidationError
-> CommandAck'ValidationError
-> CommandAck'ValidationError
-> [CommandAck'ValidationError]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandAck'ValidationError where
fieldDefault :: CommandAck'ValidationError
fieldDefault = CommandAck'ValidationError
CommandAck'UncompressedSizeCorruption
instance Control.DeepSeq.NFData CommandAck'ValidationError where
rnf :: CommandAck'ValidationError -> ()
rnf x__ :: CommandAck'ValidationError
x__ = CommandAck'ValidationError -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandAck'ValidationError
x__ ()
data CommandAckResponse
= CommandAckResponse'_constructor {CommandAckResponse -> Word64
_CommandAckResponse'consumerId :: !Data.Word.Word64,
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAckResponse -> Maybe ServerError
_CommandAckResponse'error :: !(Prelude.Maybe ServerError),
CommandAckResponse -> Maybe Text
_CommandAckResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandAckResponse -> FieldSet
_CommandAckResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAckResponse -> CommandAckResponse -> Bool
(CommandAckResponse -> CommandAckResponse -> Bool)
-> (CommandAckResponse -> CommandAckResponse -> Bool)
-> Eq CommandAckResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAckResponse -> CommandAckResponse -> Bool
$c/= :: CommandAckResponse -> CommandAckResponse -> Bool
== :: CommandAckResponse -> CommandAckResponse -> Bool
$c== :: CommandAckResponse -> CommandAckResponse -> Bool
Prelude.Eq, Eq CommandAckResponse
Eq CommandAckResponse =>
(CommandAckResponse -> CommandAckResponse -> Ordering)
-> (CommandAckResponse -> CommandAckResponse -> Bool)
-> (CommandAckResponse -> CommandAckResponse -> Bool)
-> (CommandAckResponse -> CommandAckResponse -> Bool)
-> (CommandAckResponse -> CommandAckResponse -> Bool)
-> (CommandAckResponse -> CommandAckResponse -> CommandAckResponse)
-> (CommandAckResponse -> CommandAckResponse -> CommandAckResponse)
-> Ord CommandAckResponse
CommandAckResponse -> CommandAckResponse -> Bool
CommandAckResponse -> CommandAckResponse -> Ordering
CommandAckResponse -> CommandAckResponse -> CommandAckResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAckResponse -> CommandAckResponse -> CommandAckResponse
$cmin :: CommandAckResponse -> CommandAckResponse -> CommandAckResponse
max :: CommandAckResponse -> CommandAckResponse -> CommandAckResponse
$cmax :: CommandAckResponse -> CommandAckResponse -> CommandAckResponse
>= :: CommandAckResponse -> CommandAckResponse -> Bool
$c>= :: CommandAckResponse -> CommandAckResponse -> Bool
> :: CommandAckResponse -> CommandAckResponse -> Bool
$c> :: CommandAckResponse -> CommandAckResponse -> Bool
<= :: CommandAckResponse -> CommandAckResponse -> Bool
$c<= :: CommandAckResponse -> CommandAckResponse -> Bool
< :: CommandAckResponse -> CommandAckResponse -> Bool
$c< :: CommandAckResponse -> CommandAckResponse -> Bool
compare :: CommandAckResponse -> CommandAckResponse -> Ordering
$ccompare :: CommandAckResponse -> CommandAckResponse -> Ordering
$cp1Ord :: Eq CommandAckResponse
Prelude.Ord)
instance Prelude.Show CommandAckResponse where
showsPrec :: Int -> CommandAckResponse -> ShowS
showsPrec _ __x :: CommandAckResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAckResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAckResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAckResponse "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandAckResponse -> f CommandAckResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Word64)
-> (CommandAckResponse -> Word64 -> CommandAckResponse)
-> Lens CommandAckResponse CommandAckResponse Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Word64
_CommandAckResponse'consumerId
(\ x__ :: CommandAckResponse
x__ y__ :: Word64
y__ -> CommandAckResponse
x__ {_CommandAckResponse'consumerId :: Word64
_CommandAckResponse'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAckResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Word64)
-> (CommandAckResponse -> Maybe Word64 -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidLeastBits
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Word64
y__ -> CommandAckResponse
x__ {_CommandAckResponse'txnidLeastBits :: Maybe Word64
_CommandAckResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAckResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Word64)
-> (CommandAckResponse -> Maybe Word64 -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidLeastBits
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Word64
y__ -> CommandAckResponse
x__ {_CommandAckResponse'txnidLeastBits :: Maybe Word64
_CommandAckResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAckResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Word64)
-> (CommandAckResponse -> Maybe Word64 -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidMostBits
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Word64
y__ -> CommandAckResponse
x__ {_CommandAckResponse'txnidMostBits :: Maybe Word64
_CommandAckResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAckResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Word64)
-> (CommandAckResponse -> Maybe Word64 -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidMostBits
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Word64
y__ -> CommandAckResponse
x__ {_CommandAckResponse'txnidMostBits :: Maybe Word64
_CommandAckResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAckResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAckResponse -> f CommandAckResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe ServerError)
-> (CommandAckResponse -> Maybe ServerError -> CommandAckResponse)
-> Lens
CommandAckResponse
CommandAckResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe ServerError
_CommandAckResponse'error
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe ServerError
y__ -> CommandAckResponse
x__ {_CommandAckResponse'error :: Maybe ServerError
_CommandAckResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAckResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe ServerError)
-> (CommandAckResponse -> Maybe ServerError -> CommandAckResponse)
-> Lens
CommandAckResponse
CommandAckResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe ServerError
_CommandAckResponse'error
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe ServerError
y__ -> CommandAckResponse
x__ {_CommandAckResponse'error :: Maybe ServerError
_CommandAckResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAckResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text) -> CommandAckResponse -> f CommandAckResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Text)
-> (CommandAckResponse -> Maybe Text -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Text
_CommandAckResponse'message
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Text
y__ -> CommandAckResponse
x__ {_CommandAckResponse'message :: Maybe Text
_CommandAckResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAckResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandAckResponse
-> f CommandAckResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAckResponse -> f CommandAckResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandAckResponse
-> f CommandAckResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAckResponse -> Maybe Text)
-> (CommandAckResponse -> Maybe Text -> CommandAckResponse)
-> Lens
CommandAckResponse CommandAckResponse (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> Maybe Text
_CommandAckResponse'message
(\ x__ :: CommandAckResponse
x__ y__ :: Maybe Text
y__ -> CommandAckResponse
x__ {_CommandAckResponse'message :: Maybe Text
_CommandAckResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAckResponse where
messageName :: Proxy CommandAckResponse -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandAckResponse"
packedMessageDescriptor :: Proxy CommandAckResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\DC2CommandAckResponse\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandAckResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAckResponse)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandAckResponse
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAckResponse Word64
-> FieldDescriptor CommandAckResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandAckResponse CommandAckResponse Word64 Word64
-> FieldAccessor CommandAckResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandAckResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAckResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAckResponse Word64
-> FieldDescriptor CommandAckResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandAckResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAckResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandAckResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAckResponse Word64
-> FieldDescriptor CommandAckResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAckResponse CommandAckResponse (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandAckResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAckResponse
error__field_descriptor :: FieldDescriptor CommandAckResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandAckResponse ServerError
-> FieldDescriptor CommandAckResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandAckResponse
CommandAckResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandAckResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandAckResponse
message__field_descriptor :: FieldDescriptor CommandAckResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAckResponse Text
-> FieldDescriptor CommandAckResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandAckResponse CommandAckResponse (Maybe Text) (Maybe Text)
-> FieldAccessor CommandAckResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandAckResponse
in
[(Tag, FieldDescriptor CommandAckResponse)]
-> Map Tag (FieldDescriptor CommandAckResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAckResponse
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAckResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAckResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAckResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandAckResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandAckResponse FieldSet
unknownFields
= (CommandAckResponse -> FieldSet)
-> (CommandAckResponse -> FieldSet -> CommandAckResponse)
-> Lens' CommandAckResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAckResponse -> FieldSet
_CommandAckResponse'_unknownFields
(\ x__ :: CommandAckResponse
x__ y__ :: FieldSet
y__ -> CommandAckResponse
x__ {_CommandAckResponse'_unknownFields :: FieldSet
_CommandAckResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandAckResponse
defMessage
= $WCommandAckResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandAckResponse
CommandAckResponse'_constructor
{_CommandAckResponse'consumerId :: Word64
_CommandAckResponse'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAckResponse'txnidLeastBits :: Maybe Word64
_CommandAckResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAckResponse'txnidMostBits :: Maybe Word64
_CommandAckResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAckResponse'error :: Maybe ServerError
_CommandAckResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandAckResponse'message :: Maybe Text
_CommandAckResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandAckResponse'_unknownFields :: FieldSet
_CommandAckResponse'_unknownFields = []}
parseMessage :: Parser CommandAckResponse
parseMessage
= let
loop ::
CommandAckResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAckResponse
loop :: CommandAckResponse -> Bool -> Parser CommandAckResponse
loop x :: CommandAckResponse
x required'consumerId :: Bool
required'consumerId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAckResponse -> Parser CommandAckResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandAckResponse CommandAckResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAckResponse
-> CommandAckResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAckResponse CommandAckResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandAckResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter CommandAckResponse CommandAckResponse Word64 Word64
-> Word64 -> CommandAckResponse -> CommandAckResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandAckResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter CommandAckResponse CommandAckResponse Word64 Word64
-> Word64 -> CommandAckResponse -> CommandAckResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAckResponse
x)
Bool
required'consumerId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter CommandAckResponse CommandAckResponse Word64 Word64
-> Word64 -> CommandAckResponse -> CommandAckResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAckResponse
x)
Bool
required'consumerId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter
CommandAckResponse CommandAckResponse ServerError ServerError
-> ServerError -> CommandAckResponse -> CommandAckResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandAckResponse
x)
Bool
required'consumerId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter CommandAckResponse CommandAckResponse Text Text
-> Text -> CommandAckResponse -> CommandAckResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandAckResponse
x)
Bool
required'consumerId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAckResponse -> Bool -> Parser CommandAckResponse
loop
(Setter CommandAckResponse CommandAckResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAckResponse
-> CommandAckResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAckResponse CommandAckResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAckResponse
x)
Bool
required'consumerId
in
Parser CommandAckResponse -> String -> Parser CommandAckResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandAckResponse -> Bool -> Parser CommandAckResponse
loop CommandAckResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandAckResponse"
buildMessage :: CommandAckResponse -> Builder
buildMessage
= \ _x :: CommandAckResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandAckResponse CommandAckResponse Word64 Word64
-> CommandAckResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandAckResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAckResponse
CommandAckResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAckResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAckResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAckResponse
CommandAckResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAckResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAckResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandAckResponse
CommandAckResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandAckResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandAckResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandAckResponse
CommandAckResponse
(Maybe Text)
(Maybe Text)
-> CommandAckResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandAckResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandAckResponse CommandAckResponse FieldSet FieldSet
-> CommandAckResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandAckResponse CommandAckResponse FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAckResponse
_x))))))
instance Control.DeepSeq.NFData CommandAckResponse where
rnf :: CommandAckResponse -> ()
rnf
= \ x__ :: CommandAckResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAckResponse -> FieldSet
_CommandAckResponse'_unknownFields CommandAckResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAckResponse -> Word64
_CommandAckResponse'consumerId CommandAckResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidLeastBits CommandAckResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAckResponse -> Maybe Word64
_CommandAckResponse'txnidMostBits CommandAckResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAckResponse -> Maybe ServerError
_CommandAckResponse'error CommandAckResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandAckResponse -> Maybe Text
_CommandAckResponse'message CommandAckResponse
x__) ())))))
data CommandActiveConsumerChange
= CommandActiveConsumerChange'_constructor {CommandActiveConsumerChange -> Word64
_CommandActiveConsumerChange'consumerId :: !Data.Word.Word64,
CommandActiveConsumerChange -> Maybe Bool
_CommandActiveConsumerChange'isActive :: !(Prelude.Maybe Prelude.Bool),
CommandActiveConsumerChange -> FieldSet
_CommandActiveConsumerChange'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
(CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> Eq CommandActiveConsumerChange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c/= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
== :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c== :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
Prelude.Eq, Eq CommandActiveConsumerChange
Eq CommandActiveConsumerChange =>
(CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Ordering)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Bool)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange)
-> (CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange)
-> Ord CommandActiveConsumerChange
CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Ordering
CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange
$cmin :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange
max :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange
$cmax :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> CommandActiveConsumerChange
>= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c>= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
> :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c> :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
<= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c<= :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
< :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
$c< :: CommandActiveConsumerChange -> CommandActiveConsumerChange -> Bool
compare :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Ordering
$ccompare :: CommandActiveConsumerChange
-> CommandActiveConsumerChange -> Ordering
$cp1Ord :: Eq CommandActiveConsumerChange
Prelude.Ord)
instance Prelude.Show CommandActiveConsumerChange where
showsPrec :: Int -> CommandActiveConsumerChange -> ShowS
showsPrec _ __x :: CommandActiveConsumerChange
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandActiveConsumerChange -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandActiveConsumerChange
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandActiveConsumerChange "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
fieldOf _
= ((Word64 -> f Word64)
-> CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandActiveConsumerChange -> Word64)
-> (CommandActiveConsumerChange
-> Word64 -> CommandActiveConsumerChange)
-> Lens
CommandActiveConsumerChange
CommandActiveConsumerChange
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandActiveConsumerChange -> Word64
_CommandActiveConsumerChange'consumerId
(\ x__ :: CommandActiveConsumerChange
x__ y__ :: Word64
y__ -> CommandActiveConsumerChange
x__ {_CommandActiveConsumerChange'consumerId :: Word64
_CommandActiveConsumerChange'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandActiveConsumerChange "isActive" Prelude.Bool where
fieldOf :: Proxy# "isActive"
-> (Bool -> f Bool)
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandActiveConsumerChange -> Maybe Bool)
-> (CommandActiveConsumerChange
-> Maybe Bool -> CommandActiveConsumerChange)
-> Lens
CommandActiveConsumerChange
CommandActiveConsumerChange
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandActiveConsumerChange -> Maybe Bool
_CommandActiveConsumerChange'isActive
(\ x__ :: CommandActiveConsumerChange
x__ y__ :: Maybe Bool
y__ -> CommandActiveConsumerChange
x__ {_CommandActiveConsumerChange'isActive :: Maybe Bool
_CommandActiveConsumerChange'isActive = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandActiveConsumerChange "maybe'isActive" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'isActive"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandActiveConsumerChange -> f CommandActiveConsumerChange)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandActiveConsumerChange
-> f CommandActiveConsumerChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandActiveConsumerChange -> Maybe Bool)
-> (CommandActiveConsumerChange
-> Maybe Bool -> CommandActiveConsumerChange)
-> Lens
CommandActiveConsumerChange
CommandActiveConsumerChange
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandActiveConsumerChange -> Maybe Bool
_CommandActiveConsumerChange'isActive
(\ x__ :: CommandActiveConsumerChange
x__ y__ :: Maybe Bool
y__ -> CommandActiveConsumerChange
x__ {_CommandActiveConsumerChange'isActive :: Maybe Bool
_CommandActiveConsumerChange'isActive = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandActiveConsumerChange where
messageName :: Proxy CommandActiveConsumerChange -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandActiveConsumerChange"
packedMessageDescriptor :: Proxy CommandActiveConsumerChange -> ByteString
packedMessageDescriptor _
= "\n\
\\ESCCommandActiveConsumerChange\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\"\n\
\\tis_active\CAN\STX \SOH(\b:\ENQfalseR\bisActive"
packedFileDescriptor :: Proxy CommandActiveConsumerChange -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandActiveConsumerChange)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandActiveConsumerChange
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandActiveConsumerChange Word64
-> FieldDescriptor CommandActiveConsumerChange
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandActiveConsumerChange
CommandActiveConsumerChange
Word64
Word64
-> FieldAccessor CommandActiveConsumerChange Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandActiveConsumerChange
isActive__field_descriptor :: FieldDescriptor CommandActiveConsumerChange
isActive__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandActiveConsumerChange Bool
-> FieldDescriptor CommandActiveConsumerChange
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"is_active"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
CommandActiveConsumerChange
CommandActiveConsumerChange
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor CommandActiveConsumerChange Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'isActive" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'isActive")) ::
Data.ProtoLens.FieldDescriptor CommandActiveConsumerChange
in
[(Tag, FieldDescriptor CommandActiveConsumerChange)]
-> Map Tag (FieldDescriptor CommandActiveConsumerChange)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandActiveConsumerChange
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandActiveConsumerChange
isActive__field_descriptor)]
unknownFields :: LensLike' f CommandActiveConsumerChange FieldSet
unknownFields
= (CommandActiveConsumerChange -> FieldSet)
-> (CommandActiveConsumerChange
-> FieldSet -> CommandActiveConsumerChange)
-> Lens' CommandActiveConsumerChange FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandActiveConsumerChange -> FieldSet
_CommandActiveConsumerChange'_unknownFields
(\ x__ :: CommandActiveConsumerChange
x__ y__ :: FieldSet
y__
-> CommandActiveConsumerChange
x__ {_CommandActiveConsumerChange'_unknownFields :: FieldSet
_CommandActiveConsumerChange'_unknownFields = FieldSet
y__})
defMessage :: CommandActiveConsumerChange
defMessage
= $WCommandActiveConsumerChange'_constructor :: Word64 -> Maybe Bool -> FieldSet -> CommandActiveConsumerChange
CommandActiveConsumerChange'_constructor
{_CommandActiveConsumerChange'consumerId :: Word64
_CommandActiveConsumerChange'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandActiveConsumerChange'isActive :: Maybe Bool
_CommandActiveConsumerChange'isActive = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandActiveConsumerChange'_unknownFields :: FieldSet
_CommandActiveConsumerChange'_unknownFields = []}
parseMessage :: Parser CommandActiveConsumerChange
parseMessage
= let
loop ::
CommandActiveConsumerChange
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandActiveConsumerChange
loop :: CommandActiveConsumerChange
-> Bool -> Parser CommandActiveConsumerChange
loop x :: CommandActiveConsumerChange
x required'consumerId :: Bool
required'consumerId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandActiveConsumerChange -> Parser CommandActiveConsumerChange
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandActiveConsumerChange
-> CommandActiveConsumerChange
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandActiveConsumerChange
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandActiveConsumerChange
-> Bool -> Parser CommandActiveConsumerChange
loop
(Setter
CommandActiveConsumerChange
CommandActiveConsumerChange
Word64
Word64
-> Word64
-> CommandActiveConsumerChange
-> CommandActiveConsumerChange
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandActiveConsumerChange
x)
Bool
Prelude.False
16
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"is_active"
CommandActiveConsumerChange
-> Bool -> Parser CommandActiveConsumerChange
loop
(Setter
CommandActiveConsumerChange CommandActiveConsumerChange Bool Bool
-> Bool
-> CommandActiveConsumerChange
-> CommandActiveConsumerChange
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "isActive" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"isActive") Bool
y CommandActiveConsumerChange
x)
Bool
required'consumerId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandActiveConsumerChange
-> Bool -> Parser CommandActiveConsumerChange
loop
(Setter
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandActiveConsumerChange
-> CommandActiveConsumerChange
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandActiveConsumerChange
x)
Bool
required'consumerId
in
Parser CommandActiveConsumerChange
-> String -> Parser CommandActiveConsumerChange
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandActiveConsumerChange
-> Bool -> Parser CommandActiveConsumerChange
loop CommandActiveConsumerChange
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandActiveConsumerChange"
buildMessage :: CommandActiveConsumerChange -> Builder
buildMessage
= \ _x :: CommandActiveConsumerChange
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandActiveConsumerChange
CommandActiveConsumerChange
Word64
Word64
-> CommandActiveConsumerChange -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandActiveConsumerChange
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandActiveConsumerChange
CommandActiveConsumerChange
(Maybe Bool)
(Maybe Bool)
-> CommandActiveConsumerChange -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'isActive" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'isActive") CommandActiveConsumerChange
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
-> CommandActiveConsumerChange -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandActiveConsumerChange
CommandActiveConsumerChange
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandActiveConsumerChange
_x)))
instance Control.DeepSeq.NFData CommandActiveConsumerChange where
rnf :: CommandActiveConsumerChange -> ()
rnf
= \ x__ :: CommandActiveConsumerChange
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandActiveConsumerChange -> FieldSet
_CommandActiveConsumerChange'_unknownFields CommandActiveConsumerChange
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandActiveConsumerChange -> Word64
_CommandActiveConsumerChange'consumerId CommandActiveConsumerChange
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandActiveConsumerChange -> Maybe Bool
_CommandActiveConsumerChange'isActive CommandActiveConsumerChange
x__) ()))
data CommandAddPartitionToTxn
= CommandAddPartitionToTxn'_constructor {CommandAddPartitionToTxn -> Word64
_CommandAddPartitionToTxn'requestId :: !Data.Word.Word64,
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddPartitionToTxn -> Vector Text
_CommandAddPartitionToTxn'partitions :: !(Data.Vector.Vector Data.Text.Text),
CommandAddPartitionToTxn -> FieldSet
_CommandAddPartitionToTxn'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
(CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> Eq CommandAddPartitionToTxn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c/= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
== :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c== :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
Prelude.Eq, Eq CommandAddPartitionToTxn
Eq CommandAddPartitionToTxn =>
(CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Ordering)
-> (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> (CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool)
-> (CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn)
-> (CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn)
-> Ord CommandAddPartitionToTxn
CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Ordering
CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
$cmin :: CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
max :: CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
$cmax :: CommandAddPartitionToTxn
-> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
>= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c>= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
> :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c> :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
<= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c<= :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
< :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
$c< :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Bool
compare :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Ordering
$ccompare :: CommandAddPartitionToTxn -> CommandAddPartitionToTxn -> Ordering
$cp1Ord :: Eq CommandAddPartitionToTxn
Prelude.Ord)
instance Prelude.Show CommandAddPartitionToTxn where
showsPrec :: Int -> CommandAddPartitionToTxn -> ShowS
showsPrec _ __x :: CommandAddPartitionToTxn
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAddPartitionToTxn -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAddPartitionToTxn
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Word64 -> f Word64)
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Word64)
-> (CommandAddPartitionToTxn -> Word64 -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn CommandAddPartitionToTxn Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Word64
_CommandAddPartitionToTxn'requestId
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Word64
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'requestId :: Word64
_CommandAddPartitionToTxn'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Maybe Word64)
-> (CommandAddPartitionToTxn
-> Maybe Word64 -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Maybe Word64)
-> (CommandAddPartitionToTxn
-> Maybe Word64 -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Maybe Word64)
-> (CommandAddPartitionToTxn
-> Maybe Word64 -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Maybe Word64
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Maybe Word64)
-> (CommandAddPartitionToTxn
-> Maybe Word64 -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Maybe Word64
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "partitions" [Data.Text.Text] where
fieldOf :: Proxy# "partitions"
-> ([Text] -> f [Text])
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Vector Text -> f (Vector Text))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> (([Text] -> f [Text]) -> Vector Text -> f (Vector Text))
-> ([Text] -> f [Text])
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Vector Text)
-> (CommandAddPartitionToTxn
-> Vector Text -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Vector Text)
(Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Vector Text
_CommandAddPartitionToTxn'partitions
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Vector Text
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'partitions :: Vector Text
_CommandAddPartitionToTxn'partitions = Vector Text
y__}))
((Vector Text -> [Text])
-> (Vector Text -> [Text] -> Vector Text)
-> Lens (Vector Text) (Vector Text) [Text] [Text]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Text -> [Text]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Text]
y__ -> [Text] -> Vector Text
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Text]
y__))
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxn "vec'partitions" (Data.Vector.Vector Data.Text.Text) where
fieldOf :: Proxy# "vec'partitions"
-> (Vector Text -> f (Vector Text))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
fieldOf _
= ((Vector Text -> f (Vector Text))
-> CommandAddPartitionToTxn -> f CommandAddPartitionToTxn)
-> ((Vector Text -> f (Vector Text))
-> Vector Text -> f (Vector Text))
-> (Vector Text -> f (Vector Text))
-> CommandAddPartitionToTxn
-> f CommandAddPartitionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxn -> Vector Text)
-> (CommandAddPartitionToTxn
-> Vector Text -> CommandAddPartitionToTxn)
-> Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Vector Text)
(Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> Vector Text
_CommandAddPartitionToTxn'partitions
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: Vector Text
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'partitions :: Vector Text
_CommandAddPartitionToTxn'partitions = Vector Text
y__}))
(Vector Text -> f (Vector Text)) -> Vector Text -> f (Vector Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAddPartitionToTxn where
messageName :: Proxy CommandAddPartitionToTxn -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandAddPartitionToTxn"
packedMessageDescriptor :: Proxy CommandAddPartitionToTxn -> ByteString
packedMessageDescriptor _
= "\n\
\\CANCommandAddPartitionToTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2\RS\n\
\\n\
\partitions\CAN\EOT \ETX(\tR\n\
\partitions"
packedFileDescriptor :: Proxy CommandAddPartitionToTxn -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAddPartitionToTxn)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandAddPartitionToTxn
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxn Word64
-> FieldDescriptor CommandAddPartitionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandAddPartitionToTxn CommandAddPartitionToTxn Word64 Word64
-> FieldAccessor CommandAddPartitionToTxn Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxn
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAddPartitionToTxn
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxn Word64
-> FieldDescriptor CommandAddPartitionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddPartitionToTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxn
txnidMostBits__field_descriptor :: FieldDescriptor CommandAddPartitionToTxn
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxn Word64
-> FieldDescriptor CommandAddPartitionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddPartitionToTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxn
partitions__field_descriptor :: FieldDescriptor CommandAddPartitionToTxn
partitions__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAddPartitionToTxn Text
-> FieldDescriptor CommandAddPartitionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partitions"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Packing
-> Lens' CommandAddPartitionToTxn [Text]
-> FieldAccessor CommandAddPartitionToTxn Text
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitions")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxn
in
[(Tag, FieldDescriptor CommandAddPartitionToTxn)]
-> Map Tag (FieldDescriptor CommandAddPartitionToTxn)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAddPartitionToTxn
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAddPartitionToTxn
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAddPartitionToTxn
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAddPartitionToTxn
partitions__field_descriptor)]
unknownFields :: LensLike' f CommandAddPartitionToTxn FieldSet
unknownFields
= (CommandAddPartitionToTxn -> FieldSet)
-> (CommandAddPartitionToTxn
-> FieldSet -> CommandAddPartitionToTxn)
-> Lens' CommandAddPartitionToTxn FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxn -> FieldSet
_CommandAddPartitionToTxn'_unknownFields
(\ x__ :: CommandAddPartitionToTxn
x__ y__ :: FieldSet
y__ -> CommandAddPartitionToTxn
x__ {_CommandAddPartitionToTxn'_unknownFields :: FieldSet
_CommandAddPartitionToTxn'_unknownFields = FieldSet
y__})
defMessage :: CommandAddPartitionToTxn
defMessage
= $WCommandAddPartitionToTxn'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Vector Text
-> FieldSet
-> CommandAddPartitionToTxn
CommandAddPartitionToTxn'_constructor
{_CommandAddPartitionToTxn'requestId :: Word64
_CommandAddPartitionToTxn'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAddPartitionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxn'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxn'partitions :: Vector Text
_CommandAddPartitionToTxn'partitions = Vector Text
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandAddPartitionToTxn'_unknownFields :: FieldSet
_CommandAddPartitionToTxn'_unknownFields = []}
parseMessage :: Parser CommandAddPartitionToTxn
parseMessage
= let
loop ::
CommandAddPartitionToTxn
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Data.Text.Text
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAddPartitionToTxn
loop :: CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop x :: CommandAddPartitionToTxn
x required'requestId :: Bool
required'requestId mutable'partitions :: Growing Vector RealWorld Text
mutable'partitions
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector Text
frozen'partitions <- IO (Vector Text) -> Parser (Vector Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text -> IO (Vector Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'partitions)
(let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAddPartitionToTxn -> Parser CommandAddPartitionToTxn
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddPartitionToTxn
-> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Vector Text)
(Vector Text)
-> Vector Text
-> CommandAddPartitionToTxn
-> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'partitions")
Vector Text
frozen'partitions
CommandAddPartitionToTxn
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop
(Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn Word64 Word64
-> Word64 -> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandAddPartitionToTxn
x)
Bool
Prelude.False
Growing Vector RealWorld Text
mutable'partitions
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop
(Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn Word64 Word64
-> Word64 -> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAddPartitionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Text
mutable'partitions
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop
(Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn Word64 Word64
-> Word64 -> CommandAddPartitionToTxn -> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAddPartitionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Text
mutable'partitions
34
-> do !Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"partitions"
Growing Vector RealWorld Text
v <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text
-> Text -> IO (Growing Vector (PrimState IO) Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'partitions Text
y)
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop CommandAddPartitionToTxn
x Bool
required'requestId Growing Vector RealWorld Text
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop
(Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddPartitionToTxn
-> CommandAddPartitionToTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddPartitionToTxn CommandAddPartitionToTxn FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAddPartitionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Text
mutable'partitions
in
Parser CommandAddPartitionToTxn
-> String -> Parser CommandAddPartitionToTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld Text
mutable'partitions <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandAddPartitionToTxn
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandAddPartitionToTxn
loop CommandAddPartitionToTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld Text
mutable'partitions)
"CommandAddPartitionToTxn"
buildMessage :: CommandAddPartitionToTxn -> Builder
buildMessage
= \ _x :: CommandAddPartitionToTxn
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandAddPartitionToTxn
CommandAddPartitionToTxn
Word64
Word64
-> CommandAddPartitionToTxn -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandAddPartitionToTxn
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
-> CommandAddPartitionToTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAddPartitionToTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Maybe Word64)
(Maybe Word64)
-> CommandAddPartitionToTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAddPartitionToTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Text -> Builder) -> Vector Text -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Text
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FoldLike
(Vector Text)
CommandAddPartitionToTxn
CommandAddPartitionToTxn
(Vector Text)
(Vector Text)
-> CommandAddPartitionToTxn -> Vector Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'partitions") CommandAddPartitionToTxn
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandAddPartitionToTxn
CommandAddPartitionToTxn
FieldSet
FieldSet
-> CommandAddPartitionToTxn -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandAddPartitionToTxn
CommandAddPartitionToTxn
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAddPartitionToTxn
_x)))))
instance Control.DeepSeq.NFData CommandAddPartitionToTxn where
rnf :: CommandAddPartitionToTxn -> ()
rnf
= \ x__ :: CommandAddPartitionToTxn
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxn -> FieldSet
_CommandAddPartitionToTxn'_unknownFields CommandAddPartitionToTxn
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxn -> Word64
_CommandAddPartitionToTxn'requestId CommandAddPartitionToTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidLeastBits CommandAddPartitionToTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxn -> Maybe Word64
_CommandAddPartitionToTxn'txnidMostBits CommandAddPartitionToTxn
x__)
(Vector Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxn -> Vector Text
_CommandAddPartitionToTxn'partitions CommandAddPartitionToTxn
x__) ()))))
data CommandAddPartitionToTxnResponse
= CommandAddPartitionToTxnResponse'_constructor {CommandAddPartitionToTxnResponse -> Word64
_CommandAddPartitionToTxnResponse'requestId :: !Data.Word.Word64,
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddPartitionToTxnResponse -> Maybe ServerError
_CommandAddPartitionToTxnResponse'error :: !(Prelude.Maybe ServerError),
CommandAddPartitionToTxnResponse -> Maybe Text
_CommandAddPartitionToTxnResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandAddPartitionToTxnResponse -> FieldSet
_CommandAddPartitionToTxnResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
(CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> Eq CommandAddPartitionToTxnResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c/= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
== :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c== :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
Prelude.Eq, Eq CommandAddPartitionToTxnResponse
Eq CommandAddPartitionToTxnResponse =>
(CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Ordering)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse)
-> (CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse)
-> Ord CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Ordering
CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
$cmin :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
max :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
$cmax :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
>= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c>= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
> :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c> :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
<= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c<= :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
< :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
$c< :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Bool
compare :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Ordering
$ccompare :: CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse -> Ordering
$cp1Ord :: Eq CommandAddPartitionToTxnResponse
Prelude.Ord)
instance Prelude.Show CommandAddPartitionToTxnResponse where
showsPrec :: Int -> CommandAddPartitionToTxnResponse -> ShowS
showsPrec _ __x :: CommandAddPartitionToTxnResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAddPartitionToTxnResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAddPartitionToTxnResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Word64)
-> (CommandAddPartitionToTxnResponse
-> Word64 -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Word64
_CommandAddPartitionToTxnResponse'requestId
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Word64
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'requestId :: Word64
_CommandAddPartitionToTxnResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Word64)
-> (CommandAddPartitionToTxnResponse
-> Maybe Word64 -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Word64)
-> (CommandAddPartitionToTxnResponse
-> Maybe Word64 -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Word64)
-> (CommandAddPartitionToTxnResponse
-> Maybe Word64 -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Word64)
-> (CommandAddPartitionToTxnResponse
-> Maybe Word64 -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe ServerError)
-> (CommandAddPartitionToTxnResponse
-> Maybe ServerError -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe ServerError
_CommandAddPartitionToTxnResponse'error
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'error :: Maybe ServerError
_CommandAddPartitionToTxnResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe ServerError)
-> (CommandAddPartitionToTxnResponse
-> Maybe ServerError -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe ServerError
_CommandAddPartitionToTxnResponse'error
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'error :: Maybe ServerError
_CommandAddPartitionToTxnResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Text)
-> (CommandAddPartitionToTxnResponse
-> Maybe Text -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Text
_CommandAddPartitionToTxnResponse'message
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Text
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'message :: Maybe Text
_CommandAddPartitionToTxnResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAddPartitionToTxnResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandAddPartitionToTxnResponse
-> f CommandAddPartitionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddPartitionToTxnResponse -> Maybe Text)
-> (CommandAddPartitionToTxnResponse
-> Maybe Text -> CommandAddPartitionToTxnResponse)
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> Maybe Text
_CommandAddPartitionToTxnResponse'message
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: Maybe Text
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'message :: Maybe Text
_CommandAddPartitionToTxnResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAddPartitionToTxnResponse where
messageName :: Proxy CommandAddPartitionToTxnResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandAddPartitionToTxnResponse"
packedMessageDescriptor :: Proxy CommandAddPartitionToTxnResponse -> ByteString
packedMessageDescriptor _
= "\n\
\ CommandAddPartitionToTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandAddPartitionToTxnResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAddPartitionToTxnResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandAddPartitionToTxnResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
-> FieldDescriptor CommandAddPartitionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxnResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAddPartitionToTxnResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
-> FieldDescriptor CommandAddPartitionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxnResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandAddPartitionToTxnResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
-> FieldDescriptor CommandAddPartitionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddPartitionToTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxnResponse
error__field_descriptor :: FieldDescriptor CommandAddPartitionToTxnResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandAddPartitionToTxnResponse ServerError
-> FieldDescriptor CommandAddPartitionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandAddPartitionToTxnResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxnResponse
message__field_descriptor :: FieldDescriptor CommandAddPartitionToTxnResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAddPartitionToTxnResponse Text
-> FieldDescriptor CommandAddPartitionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandAddPartitionToTxnResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandAddPartitionToTxnResponse
in
[(Tag, FieldDescriptor CommandAddPartitionToTxnResponse)]
-> Map Tag (FieldDescriptor CommandAddPartitionToTxnResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAddPartitionToTxnResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAddPartitionToTxnResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAddPartitionToTxnResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAddPartitionToTxnResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandAddPartitionToTxnResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandAddPartitionToTxnResponse FieldSet
unknownFields
= (CommandAddPartitionToTxnResponse -> FieldSet)
-> (CommandAddPartitionToTxnResponse
-> FieldSet -> CommandAddPartitionToTxnResponse)
-> Lens' CommandAddPartitionToTxnResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddPartitionToTxnResponse -> FieldSet
_CommandAddPartitionToTxnResponse'_unknownFields
(\ x__ :: CommandAddPartitionToTxnResponse
x__ y__ :: FieldSet
y__
-> CommandAddPartitionToTxnResponse
x__ {_CommandAddPartitionToTxnResponse'_unknownFields :: FieldSet
_CommandAddPartitionToTxnResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandAddPartitionToTxnResponse
defMessage
= $WCommandAddPartitionToTxnResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse'_constructor
{_CommandAddPartitionToTxnResponse'requestId :: Word64
_CommandAddPartitionToTxnResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAddPartitionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxnResponse'error :: Maybe ServerError
_CommandAddPartitionToTxnResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxnResponse'message :: Maybe Text
_CommandAddPartitionToTxnResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandAddPartitionToTxnResponse'_unknownFields :: FieldSet
_CommandAddPartitionToTxnResponse'_unknownFields = []}
parseMessage :: Parser CommandAddPartitionToTxnResponse
parseMessage
= let
loop ::
CommandAddPartitionToTxnResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAddPartitionToTxnResponse
loop :: CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop x :: CommandAddPartitionToTxnResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAddPartitionToTxnResponse
-> Parser CommandAddPartitionToTxnResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandAddPartitionToTxnResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandAddPartitionToTxnResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAddPartitionToTxnResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAddPartitionToTxnResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
ServerError
ServerError
-> ServerError
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandAddPartitionToTxnResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Text
Text
-> Text
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandAddPartitionToTxnResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop
(Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddPartitionToTxnResponse
-> CommandAddPartitionToTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAddPartitionToTxnResponse
x)
Bool
required'requestId
in
Parser CommandAddPartitionToTxnResponse
-> String -> Parser CommandAddPartitionToTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandAddPartitionToTxnResponse
-> Bool -> Parser CommandAddPartitionToTxnResponse
loop CommandAddPartitionToTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandAddPartitionToTxnResponse"
buildMessage :: CommandAddPartitionToTxnResponse -> Builder
buildMessage
= \ _x :: CommandAddPartitionToTxnResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
Word64
Word64
-> CommandAddPartitionToTxnResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandAddPartitionToTxnResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAddPartitionToTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAddPartitionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAddPartitionToTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAddPartitionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandAddPartitionToTxnResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandAddPartitionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
(Maybe Text)
(Maybe Text)
-> CommandAddPartitionToTxnResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandAddPartitionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
-> CommandAddPartitionToTxnResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandAddPartitionToTxnResponse
CommandAddPartitionToTxnResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAddPartitionToTxnResponse
_x))))))
instance Control.DeepSeq.NFData CommandAddPartitionToTxnResponse where
rnf :: CommandAddPartitionToTxnResponse -> ()
rnf
= \ x__ :: CommandAddPartitionToTxnResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> FieldSet
_CommandAddPartitionToTxnResponse'_unknownFields CommandAddPartitionToTxnResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> Word64
_CommandAddPartitionToTxnResponse'requestId CommandAddPartitionToTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidLeastBits CommandAddPartitionToTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> Maybe Word64
_CommandAddPartitionToTxnResponse'txnidMostBits CommandAddPartitionToTxnResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> Maybe ServerError
_CommandAddPartitionToTxnResponse'error CommandAddPartitionToTxnResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddPartitionToTxnResponse -> Maybe Text
_CommandAddPartitionToTxnResponse'message CommandAddPartitionToTxnResponse
x__) ())))))
data CommandAddSubscriptionToTxn
= CommandAddSubscriptionToTxn'_constructor {CommandAddSubscriptionToTxn -> Word64
_CommandAddSubscriptionToTxn'requestId :: !Data.Word.Word64,
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddSubscriptionToTxn -> Vector Subscription
_CommandAddSubscriptionToTxn'subscription :: !(Data.Vector.Vector Subscription),
CommandAddSubscriptionToTxn -> FieldSet
_CommandAddSubscriptionToTxn'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
(CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> Eq CommandAddSubscriptionToTxn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c/= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
== :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c== :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
Prelude.Eq, Eq CommandAddSubscriptionToTxn
Eq CommandAddSubscriptionToTxn =>
(CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Ordering)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Bool)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn)
-> (CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn)
-> Ord CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Ordering
CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn
$cmin :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn
max :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn
$cmax :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn
>= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c>= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
> :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c> :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
<= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c<= :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
< :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
$c< :: CommandAddSubscriptionToTxn -> CommandAddSubscriptionToTxn -> Bool
compare :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Ordering
$ccompare :: CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn -> Ordering
$cp1Ord :: Eq CommandAddSubscriptionToTxn
Prelude.Ord)
instance Prelude.Show CommandAddSubscriptionToTxn where
showsPrec :: Int -> CommandAddSubscriptionToTxn -> ShowS
showsPrec _ __x :: CommandAddSubscriptionToTxn
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAddSubscriptionToTxn -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAddSubscriptionToTxn
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Word64 -> f Word64)
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Word64)
-> (CommandAddSubscriptionToTxn
-> Word64 -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Word64
_CommandAddSubscriptionToTxn'requestId
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Word64
y__ -> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'requestId :: Word64
_CommandAddSubscriptionToTxn'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Maybe Word64)
-> (CommandAddSubscriptionToTxn
-> Maybe Word64 -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Maybe Word64)
-> (CommandAddSubscriptionToTxn
-> Maybe Word64 -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Maybe Word64)
-> (CommandAddSubscriptionToTxn
-> Maybe Word64 -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Maybe Word64)
-> (CommandAddSubscriptionToTxn
-> Maybe Word64 -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "subscription" [Subscription] where
fieldOf :: Proxy# "subscription"
-> ([Subscription] -> f [Subscription])
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Vector Subscription -> f (Vector Subscription))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> (([Subscription] -> f [Subscription])
-> Vector Subscription -> f (Vector Subscription))
-> ([Subscription] -> f [Subscription])
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Vector Subscription)
-> (CommandAddSubscriptionToTxn
-> Vector Subscription -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Vector Subscription)
(Vector Subscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Vector Subscription
_CommandAddSubscriptionToTxn'subscription
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Vector Subscription
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'subscription :: Vector Subscription
_CommandAddSubscriptionToTxn'subscription = Vector Subscription
y__}))
((Vector Subscription -> [Subscription])
-> (Vector Subscription -> [Subscription] -> Vector Subscription)
-> Lens
(Vector Subscription)
(Vector Subscription)
[Subscription]
[Subscription]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Subscription -> [Subscription]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Subscription]
y__ -> [Subscription] -> Vector Subscription
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Subscription]
y__))
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxn "vec'subscription" (Data.Vector.Vector Subscription) where
fieldOf :: Proxy# "vec'subscription"
-> (Vector Subscription -> f (Vector Subscription))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
fieldOf _
= ((Vector Subscription -> f (Vector Subscription))
-> CommandAddSubscriptionToTxn -> f CommandAddSubscriptionToTxn)
-> ((Vector Subscription -> f (Vector Subscription))
-> Vector Subscription -> f (Vector Subscription))
-> (Vector Subscription -> f (Vector Subscription))
-> CommandAddSubscriptionToTxn
-> f CommandAddSubscriptionToTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxn -> Vector Subscription)
-> (CommandAddSubscriptionToTxn
-> Vector Subscription -> CommandAddSubscriptionToTxn)
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Vector Subscription)
(Vector Subscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> Vector Subscription
_CommandAddSubscriptionToTxn'subscription
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: Vector Subscription
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'subscription :: Vector Subscription
_CommandAddSubscriptionToTxn'subscription = Vector Subscription
y__}))
(Vector Subscription -> f (Vector Subscription))
-> Vector Subscription -> f (Vector Subscription)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAddSubscriptionToTxn where
messageName :: Proxy CommandAddSubscriptionToTxn -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandAddSubscriptionToTxn"
packedMessageDescriptor :: Proxy CommandAddSubscriptionToTxn -> ByteString
packedMessageDescriptor _
= "\n\
\\ESCCommandAddSubscriptionToTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2>\n\
\\fsubscription\CAN\EOT \ETX(\v2\SUB.pulsar.proto.SubscriptionR\fsubscription"
packedFileDescriptor :: Proxy CommandAddSubscriptionToTxn -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAddSubscriptionToTxn)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxn
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxn Word64
-> FieldDescriptor CommandAddSubscriptionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
-> FieldAccessor CommandAddSubscriptionToTxn Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxn
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxn
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxn Word64
-> FieldDescriptor CommandAddSubscriptionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddSubscriptionToTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxn
txnidMostBits__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxn
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxn Word64
-> FieldDescriptor CommandAddSubscriptionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddSubscriptionToTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxn
subscription__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxn
subscription__field_descriptor
= String
-> FieldTypeDescriptor Subscription
-> FieldAccessor CommandAddSubscriptionToTxn Subscription
-> FieldDescriptor CommandAddSubscriptionToTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subscription"
(MessageOrGroup -> FieldTypeDescriptor Subscription
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Subscription)
(Packing
-> Lens' CommandAddSubscriptionToTxn [Subscription]
-> FieldAccessor CommandAddSubscriptionToTxn Subscription
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxn
in
[(Tag, FieldDescriptor CommandAddSubscriptionToTxn)]
-> Map Tag (FieldDescriptor CommandAddSubscriptionToTxn)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAddSubscriptionToTxn
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAddSubscriptionToTxn
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAddSubscriptionToTxn
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAddSubscriptionToTxn
subscription__field_descriptor)]
unknownFields :: LensLike' f CommandAddSubscriptionToTxn FieldSet
unknownFields
= (CommandAddSubscriptionToTxn -> FieldSet)
-> (CommandAddSubscriptionToTxn
-> FieldSet -> CommandAddSubscriptionToTxn)
-> Lens' CommandAddSubscriptionToTxn FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxn -> FieldSet
_CommandAddSubscriptionToTxn'_unknownFields
(\ x__ :: CommandAddSubscriptionToTxn
x__ y__ :: FieldSet
y__
-> CommandAddSubscriptionToTxn
x__ {_CommandAddSubscriptionToTxn'_unknownFields :: FieldSet
_CommandAddSubscriptionToTxn'_unknownFields = FieldSet
y__})
defMessage :: CommandAddSubscriptionToTxn
defMessage
= $WCommandAddSubscriptionToTxn'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Vector Subscription
-> FieldSet
-> CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn'_constructor
{_CommandAddSubscriptionToTxn'requestId :: Word64
_CommandAddSubscriptionToTxn'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAddSubscriptionToTxn'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxn'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxn'subscription :: Vector Subscription
_CommandAddSubscriptionToTxn'subscription = Vector Subscription
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandAddSubscriptionToTxn'_unknownFields :: FieldSet
_CommandAddSubscriptionToTxn'_unknownFields = []}
parseMessage :: Parser CommandAddSubscriptionToTxn
parseMessage
= let
loop ::
CommandAddSubscriptionToTxn
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Subscription
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAddSubscriptionToTxn
loop :: CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop x :: CommandAddSubscriptionToTxn
x required'requestId :: Bool
required'requestId mutable'subscription :: Growing Vector RealWorld Subscription
mutable'subscription
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector Subscription
frozen'subscription <- IO (Vector Subscription) -> Parser (Vector Subscription)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Subscription
-> IO (Vector Subscription)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Subscription
Growing Vector (PrimState IO) Subscription
mutable'subscription)
(let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAddSubscriptionToTxn -> Parser CommandAddSubscriptionToTxn
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Vector Subscription)
(Vector Subscription)
-> Vector Subscription
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'subscription")
Vector Subscription
frozen'subscription
CommandAddSubscriptionToTxn
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandAddSubscriptionToTxn
x)
Bool
Prelude.False
Growing Vector RealWorld Subscription
mutable'subscription
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAddSubscriptionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Subscription
mutable'subscription
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAddSubscriptionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Subscription
mutable'subscription
34
-> do !Subscription
y <- Parser Subscription -> String -> Parser Subscription
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Subscription -> Parser Subscription
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser Subscription
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"subscription"
Growing Vector RealWorld Subscription
v <- IO (Growing Vector RealWorld Subscription)
-> Parser (Growing Vector RealWorld Subscription)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Subscription
-> Subscription -> IO (Growing Vector (PrimState IO) Subscription)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
Growing Vector RealWorld Subscription
Growing Vector (PrimState IO) Subscription
mutable'subscription Subscription
y)
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop CommandAddSubscriptionToTxn
x Bool
required'requestId Growing Vector RealWorld Subscription
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop
(Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddSubscriptionToTxn
-> CommandAddSubscriptionToTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAddSubscriptionToTxn
x)
Bool
required'requestId
Growing Vector RealWorld Subscription
mutable'subscription
in
Parser CommandAddSubscriptionToTxn
-> String -> Parser CommandAddSubscriptionToTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld Subscription
mutable'subscription <- IO (Growing Vector RealWorld Subscription)
-> Parser (Growing Vector RealWorld Subscription)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Subscription)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandAddSubscriptionToTxn
-> Bool
-> Growing Vector RealWorld Subscription
-> Parser CommandAddSubscriptionToTxn
loop CommandAddSubscriptionToTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld Subscription
mutable'subscription)
"CommandAddSubscriptionToTxn"
buildMessage :: CommandAddSubscriptionToTxn -> Builder
buildMessage
= \ _x :: CommandAddSubscriptionToTxn
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
Word64
Word64
-> CommandAddSubscriptionToTxn -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandAddSubscriptionToTxn
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
-> CommandAddSubscriptionToTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAddSubscriptionToTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Maybe Word64)
(Maybe Word64)
-> CommandAddSubscriptionToTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAddSubscriptionToTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Subscription -> Builder) -> Vector Subscription -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Subscription
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder)
-> (Subscription -> ByteString) -> Subscription -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Subscription -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Subscription
_v))
(FoldLike
(Vector Subscription)
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
(Vector Subscription)
(Vector Subscription)
-> CommandAddSubscriptionToTxn -> Vector Subscription
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'subscription") CommandAddSubscriptionToTxn
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
-> CommandAddSubscriptionToTxn -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandAddSubscriptionToTxn
CommandAddSubscriptionToTxn
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAddSubscriptionToTxn
_x)))))
instance Control.DeepSeq.NFData CommandAddSubscriptionToTxn where
rnf :: CommandAddSubscriptionToTxn -> ()
rnf
= \ x__ :: CommandAddSubscriptionToTxn
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxn -> FieldSet
_CommandAddSubscriptionToTxn'_unknownFields CommandAddSubscriptionToTxn
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxn -> Word64
_CommandAddSubscriptionToTxn'requestId CommandAddSubscriptionToTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidLeastBits CommandAddSubscriptionToTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxn -> Maybe Word64
_CommandAddSubscriptionToTxn'txnidMostBits CommandAddSubscriptionToTxn
x__)
(Vector Subscription -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxn -> Vector Subscription
_CommandAddSubscriptionToTxn'subscription CommandAddSubscriptionToTxn
x__) ()))))
data CommandAddSubscriptionToTxnResponse
= CommandAddSubscriptionToTxnResponse'_constructor {CommandAddSubscriptionToTxnResponse -> Word64
_CommandAddSubscriptionToTxnResponse'requestId :: !Data.Word.Word64,
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandAddSubscriptionToTxnResponse -> Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error :: !(Prelude.Maybe ServerError),
CommandAddSubscriptionToTxnResponse -> Maybe Text
_CommandAddSubscriptionToTxnResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandAddSubscriptionToTxnResponse -> FieldSet
_CommandAddSubscriptionToTxnResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
(CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> Eq CommandAddSubscriptionToTxnResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c/= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
== :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c== :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
Prelude.Eq, Eq CommandAddSubscriptionToTxnResponse
Eq CommandAddSubscriptionToTxnResponse =>
(CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Ordering)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse)
-> (CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse)
-> Ord CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Ordering
CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
$cmin :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
max :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
$cmax :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
>= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c>= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
> :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c> :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
<= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c<= :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
< :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
$c< :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Bool
compare :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Ordering
$ccompare :: CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse -> Ordering
$cp1Ord :: Eq CommandAddSubscriptionToTxnResponse
Prelude.Ord)
instance Prelude.Show CommandAddSubscriptionToTxnResponse where
showsPrec :: Int -> CommandAddSubscriptionToTxnResponse -> ShowS
showsPrec _ __x :: CommandAddSubscriptionToTxnResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAddSubscriptionToTxnResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAddSubscriptionToTxnResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Word64)
-> (CommandAddSubscriptionToTxnResponse
-> Word64 -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Word64
_CommandAddSubscriptionToTxnResponse'requestId
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Word64
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'requestId :: Word64
_CommandAddSubscriptionToTxnResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Word64)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Word64 -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxnResponse
x__
{_CommandAddSubscriptionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Word64)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Word64 -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxnResponse
x__
{_CommandAddSubscriptionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Word64)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Word64 -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Word64)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Word64 -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Word64
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe ServerError)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe ServerError -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe ServerError
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'error :: Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe ServerError)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe ServerError -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe ServerError
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'error :: Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Text)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Text -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Text
_CommandAddSubscriptionToTxnResponse'message
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Text
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'message :: Maybe Text
_CommandAddSubscriptionToTxnResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAddSubscriptionToTxnResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandAddSubscriptionToTxnResponse
-> f CommandAddSubscriptionToTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAddSubscriptionToTxnResponse -> Maybe Text)
-> (CommandAddSubscriptionToTxnResponse
-> Maybe Text -> CommandAddSubscriptionToTxnResponse)
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> Maybe Text
_CommandAddSubscriptionToTxnResponse'message
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: Maybe Text
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'message :: Maybe Text
_CommandAddSubscriptionToTxnResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAddSubscriptionToTxnResponse where
messageName :: Proxy CommandAddSubscriptionToTxnResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandAddSubscriptionToTxnResponse"
packedMessageDescriptor :: Proxy CommandAddSubscriptionToTxnResponse -> ByteString
packedMessageDescriptor _
= "\n\
\#CommandAddSubscriptionToTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandAddSubscriptionToTxnResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAddSubscriptionToTxnResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxnResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
-> FieldDescriptor CommandAddSubscriptionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
-> FieldDescriptor CommandAddSubscriptionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
-> FieldDescriptor CommandAddSubscriptionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandAddSubscriptionToTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxnResponse
error__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxnResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandAddSubscriptionToTxnResponse ServerError
-> FieldDescriptor CommandAddSubscriptionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandAddSubscriptionToTxnResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxnResponse
message__field_descriptor :: FieldDescriptor CommandAddSubscriptionToTxnResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAddSubscriptionToTxnResponse Text
-> FieldDescriptor CommandAddSubscriptionToTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandAddSubscriptionToTxnResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandAddSubscriptionToTxnResponse
in
[(Tag, FieldDescriptor CommandAddSubscriptionToTxnResponse)]
-> Map Tag (FieldDescriptor CommandAddSubscriptionToTxnResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAddSubscriptionToTxnResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAddSubscriptionToTxnResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandAddSubscriptionToTxnResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandAddSubscriptionToTxnResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandAddSubscriptionToTxnResponse FieldSet
unknownFields
= (CommandAddSubscriptionToTxnResponse -> FieldSet)
-> (CommandAddSubscriptionToTxnResponse
-> FieldSet -> CommandAddSubscriptionToTxnResponse)
-> Lens' CommandAddSubscriptionToTxnResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAddSubscriptionToTxnResponse -> FieldSet
_CommandAddSubscriptionToTxnResponse'_unknownFields
(\ x__ :: CommandAddSubscriptionToTxnResponse
x__ y__ :: FieldSet
y__
-> CommandAddSubscriptionToTxnResponse
x__ {_CommandAddSubscriptionToTxnResponse'_unknownFields :: FieldSet
_CommandAddSubscriptionToTxnResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandAddSubscriptionToTxnResponse
defMessage
= $WCommandAddSubscriptionToTxnResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse'_constructor
{_CommandAddSubscriptionToTxnResponse'requestId :: Word64
_CommandAddSubscriptionToTxnResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandAddSubscriptionToTxnResponse'txnidLeastBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxnResponse'txnidMostBits :: Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxnResponse'error :: Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxnResponse'message :: Maybe Text
_CommandAddSubscriptionToTxnResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandAddSubscriptionToTxnResponse'_unknownFields :: FieldSet
_CommandAddSubscriptionToTxnResponse'_unknownFields = []}
parseMessage :: Parser CommandAddSubscriptionToTxnResponse
parseMessage
= let
loop ::
CommandAddSubscriptionToTxnResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAddSubscriptionToTxnResponse
loop :: CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop x :: CommandAddSubscriptionToTxnResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandAddSubscriptionToTxnResponse
-> Parser CommandAddSubscriptionToTxnResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandAddSubscriptionToTxnResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandAddSubscriptionToTxnResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandAddSubscriptionToTxnResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
-> Word64
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandAddSubscriptionToTxnResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
ServerError
ServerError
-> ServerError
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandAddSubscriptionToTxnResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Text
Text
-> Text
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandAddSubscriptionToTxnResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop
(Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandAddSubscriptionToTxnResponse
-> CommandAddSubscriptionToTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAddSubscriptionToTxnResponse
x)
Bool
required'requestId
in
Parser CommandAddSubscriptionToTxnResponse
-> String -> Parser CommandAddSubscriptionToTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandAddSubscriptionToTxnResponse
-> Bool -> Parser CommandAddSubscriptionToTxnResponse
loop CommandAddSubscriptionToTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandAddSubscriptionToTxnResponse"
buildMessage :: CommandAddSubscriptionToTxnResponse -> Builder
buildMessage
= \ _x :: CommandAddSubscriptionToTxnResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
Word64
Word64
-> CommandAddSubscriptionToTxnResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandAddSubscriptionToTxnResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAddSubscriptionToTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandAddSubscriptionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandAddSubscriptionToTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandAddSubscriptionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandAddSubscriptionToTxnResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandAddSubscriptionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
(Maybe Text)
(Maybe Text)
-> CommandAddSubscriptionToTxnResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandAddSubscriptionToTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
-> CommandAddSubscriptionToTxnResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandAddSubscriptionToTxnResponse
CommandAddSubscriptionToTxnResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAddSubscriptionToTxnResponse
_x))))))
instance Control.DeepSeq.NFData CommandAddSubscriptionToTxnResponse where
rnf :: CommandAddSubscriptionToTxnResponse -> ()
rnf
= \ x__ :: CommandAddSubscriptionToTxnResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> FieldSet
_CommandAddSubscriptionToTxnResponse'_unknownFields CommandAddSubscriptionToTxnResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> Word64
_CommandAddSubscriptionToTxnResponse'requestId CommandAddSubscriptionToTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidLeastBits CommandAddSubscriptionToTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> Maybe Word64
_CommandAddSubscriptionToTxnResponse'txnidMostBits CommandAddSubscriptionToTxnResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> Maybe ServerError
_CommandAddSubscriptionToTxnResponse'error CommandAddSubscriptionToTxnResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAddSubscriptionToTxnResponse -> Maybe Text
_CommandAddSubscriptionToTxnResponse'message CommandAddSubscriptionToTxnResponse
x__) ())))))
data CommandAuthChallenge
= CommandAuthChallenge'_constructor {CommandAuthChallenge -> Maybe Text
_CommandAuthChallenge'serverVersion :: !(Prelude.Maybe Data.Text.Text),
CommandAuthChallenge -> Maybe AuthData
_CommandAuthChallenge'challenge :: !(Prelude.Maybe AuthData),
CommandAuthChallenge -> Maybe Int32
_CommandAuthChallenge'protocolVersion :: !(Prelude.Maybe Data.Int.Int32),
CommandAuthChallenge -> FieldSet
_CommandAuthChallenge'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAuthChallenge -> CommandAuthChallenge -> Bool
(CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> (CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> Eq CommandAuthChallenge
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c/= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
== :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c== :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
Prelude.Eq, Eq CommandAuthChallenge
Eq CommandAuthChallenge =>
(CommandAuthChallenge -> CommandAuthChallenge -> Ordering)
-> (CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> (CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> (CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> (CommandAuthChallenge -> CommandAuthChallenge -> Bool)
-> (CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge)
-> (CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge)
-> Ord CommandAuthChallenge
CommandAuthChallenge -> CommandAuthChallenge -> Bool
CommandAuthChallenge -> CommandAuthChallenge -> Ordering
CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge
$cmin :: CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge
max :: CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge
$cmax :: CommandAuthChallenge
-> CommandAuthChallenge -> CommandAuthChallenge
>= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c>= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
> :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c> :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
<= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c<= :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
< :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
$c< :: CommandAuthChallenge -> CommandAuthChallenge -> Bool
compare :: CommandAuthChallenge -> CommandAuthChallenge -> Ordering
$ccompare :: CommandAuthChallenge -> CommandAuthChallenge -> Ordering
$cp1Ord :: Eq CommandAuthChallenge
Prelude.Ord)
instance Prelude.Show CommandAuthChallenge where
showsPrec :: Int -> CommandAuthChallenge -> ShowS
showsPrec _ __x :: CommandAuthChallenge
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAuthChallenge -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAuthChallenge
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "serverVersion" Data.Text.Text where
fieldOf :: Proxy# "serverVersion"
-> (Text -> f Text)
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe Text)
-> (CommandAuthChallenge -> Maybe Text -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge CommandAuthChallenge (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe Text
_CommandAuthChallenge'serverVersion
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe Text
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'serverVersion :: Maybe Text
_CommandAuthChallenge'serverVersion = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "maybe'serverVersion" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'serverVersion"
-> (Maybe Text -> f (Maybe Text))
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe Text)
-> (CommandAuthChallenge -> Maybe Text -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge CommandAuthChallenge (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe Text
_CommandAuthChallenge'serverVersion
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe Text
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'serverVersion :: Maybe Text
_CommandAuthChallenge'serverVersion = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "challenge" AuthData where
fieldOf :: Proxy# "challenge"
-> (AuthData -> f AuthData)
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((AuthData -> f AuthData)
-> Maybe AuthData -> f (Maybe AuthData))
-> (AuthData -> f AuthData)
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe AuthData)
-> (CommandAuthChallenge -> Maybe AuthData -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe AuthData)
(Maybe AuthData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe AuthData
_CommandAuthChallenge'challenge
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe AuthData
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'challenge :: Maybe AuthData
_CommandAuthChallenge'challenge = Maybe AuthData
y__}))
(AuthData -> Lens' (Maybe AuthData) AuthData
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens AuthData
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "maybe'challenge" (Prelude.Maybe AuthData) where
fieldOf :: Proxy# "maybe'challenge"
-> (Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((Maybe AuthData -> f (Maybe AuthData))
-> Maybe AuthData -> f (Maybe AuthData))
-> (Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe AuthData)
-> (CommandAuthChallenge -> Maybe AuthData -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe AuthData)
(Maybe AuthData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe AuthData
_CommandAuthChallenge'challenge
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe AuthData
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'challenge :: Maybe AuthData
_CommandAuthChallenge'challenge = Maybe AuthData
y__}))
(Maybe AuthData -> f (Maybe AuthData))
-> Maybe AuthData -> f (Maybe AuthData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "protocolVersion" Data.Int.Int32 where
fieldOf :: Proxy# "protocolVersion"
-> (Int32 -> f Int32)
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe Int32)
-> (CommandAuthChallenge -> Maybe Int32 -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe Int32)
(Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe Int32
_CommandAuthChallenge'protocolVersion
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe Int32
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'protocolVersion :: Maybe Int32
_CommandAuthChallenge'protocolVersion = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAuthChallenge "maybe'protocolVersion" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'protocolVersion"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandAuthChallenge
-> f CommandAuthChallenge
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandAuthChallenge -> f CommandAuthChallenge)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandAuthChallenge
-> f CommandAuthChallenge
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthChallenge -> Maybe Int32)
-> (CommandAuthChallenge -> Maybe Int32 -> CommandAuthChallenge)
-> Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe Int32)
(Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> Maybe Int32
_CommandAuthChallenge'protocolVersion
(\ x__ :: CommandAuthChallenge
x__ y__ :: Maybe Int32
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'protocolVersion :: Maybe Int32
_CommandAuthChallenge'protocolVersion = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAuthChallenge where
messageName :: Proxy CommandAuthChallenge -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandAuthChallenge"
packedMessageDescriptor :: Proxy CommandAuthChallenge -> ByteString
packedMessageDescriptor _
= "\n\
\\DC4CommandAuthChallenge\DC2%\n\
\\SOserver_version\CAN\SOH \SOH(\tR\rserverVersion\DC24\n\
\\tchallenge\CAN\STX \SOH(\v2\SYN.pulsar.proto.AuthDataR\tchallenge\DC2,\n\
\\DLEprotocol_version\CAN\ETX \SOH(\ENQ:\SOH0R\SIprotocolVersion"
packedFileDescriptor :: Proxy CommandAuthChallenge -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAuthChallenge)
fieldsByTag
= let
serverVersion__field_descriptor :: FieldDescriptor CommandAuthChallenge
serverVersion__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAuthChallenge Text
-> FieldDescriptor CommandAuthChallenge
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"server_version"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandAuthChallenge CommandAuthChallenge (Maybe Text) (Maybe Text)
-> FieldAccessor CommandAuthChallenge Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'serverVersion")) ::
Data.ProtoLens.FieldDescriptor CommandAuthChallenge
challenge__field_descriptor :: FieldDescriptor CommandAuthChallenge
challenge__field_descriptor
= String
-> FieldTypeDescriptor AuthData
-> FieldAccessor CommandAuthChallenge AuthData
-> FieldDescriptor CommandAuthChallenge
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"challenge"
(MessageOrGroup -> FieldTypeDescriptor AuthData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AuthData)
(Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe AuthData)
(Maybe AuthData)
-> FieldAccessor CommandAuthChallenge AuthData
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'challenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'challenge")) ::
Data.ProtoLens.FieldDescriptor CommandAuthChallenge
protocolVersion__field_descriptor :: FieldDescriptor CommandAuthChallenge
protocolVersion__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandAuthChallenge Int32
-> FieldDescriptor CommandAuthChallenge
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"protocol_version"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens
CommandAuthChallenge
CommandAuthChallenge
(Maybe Int32)
(Maybe Int32)
-> FieldAccessor CommandAuthChallenge Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion")) ::
Data.ProtoLens.FieldDescriptor CommandAuthChallenge
in
[(Tag, FieldDescriptor CommandAuthChallenge)]
-> Map Tag (FieldDescriptor CommandAuthChallenge)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAuthChallenge
serverVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAuthChallenge
challenge__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAuthChallenge
protocolVersion__field_descriptor)]
unknownFields :: LensLike' f CommandAuthChallenge FieldSet
unknownFields
= (CommandAuthChallenge -> FieldSet)
-> (CommandAuthChallenge -> FieldSet -> CommandAuthChallenge)
-> Lens' CommandAuthChallenge FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthChallenge -> FieldSet
_CommandAuthChallenge'_unknownFields
(\ x__ :: CommandAuthChallenge
x__ y__ :: FieldSet
y__ -> CommandAuthChallenge
x__ {_CommandAuthChallenge'_unknownFields :: FieldSet
_CommandAuthChallenge'_unknownFields = FieldSet
y__})
defMessage :: CommandAuthChallenge
defMessage
= $WCommandAuthChallenge'_constructor :: Maybe Text
-> Maybe AuthData
-> Maybe Int32
-> FieldSet
-> CommandAuthChallenge
CommandAuthChallenge'_constructor
{_CommandAuthChallenge'serverVersion :: Maybe Text
_CommandAuthChallenge'serverVersion = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandAuthChallenge'challenge :: Maybe AuthData
_CommandAuthChallenge'challenge = Maybe AuthData
forall a. Maybe a
Prelude.Nothing,
_CommandAuthChallenge'protocolVersion :: Maybe Int32
_CommandAuthChallenge'protocolVersion = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandAuthChallenge'_unknownFields :: FieldSet
_CommandAuthChallenge'_unknownFields = []}
parseMessage :: Parser CommandAuthChallenge
parseMessage
= let
loop ::
CommandAuthChallenge
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAuthChallenge
loop :: CommandAuthChallenge -> Parser CommandAuthChallenge
loop x :: CommandAuthChallenge
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
CommandAuthChallenge -> Parser CommandAuthChallenge
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandAuthChallenge CommandAuthChallenge FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAuthChallenge
-> CommandAuthChallenge
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAuthChallenge CommandAuthChallenge FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandAuthChallenge
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"server_version"
CommandAuthChallenge -> Parser CommandAuthChallenge
loop
(Setter CommandAuthChallenge CommandAuthChallenge Text Text
-> Text -> CommandAuthChallenge -> CommandAuthChallenge
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"serverVersion") Text
y CommandAuthChallenge
x)
18
-> do AuthData
y <- Parser AuthData -> String -> Parser AuthData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AuthData -> Parser AuthData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser AuthData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"challenge"
CommandAuthChallenge -> Parser CommandAuthChallenge
loop
(Setter CommandAuthChallenge CommandAuthChallenge AuthData AuthData
-> AuthData -> CommandAuthChallenge -> CommandAuthChallenge
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "challenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"challenge") AuthData
y CommandAuthChallenge
x)
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"protocol_version"
CommandAuthChallenge -> Parser CommandAuthChallenge
loop
(Setter CommandAuthChallenge CommandAuthChallenge Int32 Int32
-> Int32 -> CommandAuthChallenge -> CommandAuthChallenge
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"protocolVersion") Int32
y CommandAuthChallenge
x)
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAuthChallenge -> Parser CommandAuthChallenge
loop
(Setter CommandAuthChallenge CommandAuthChallenge FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAuthChallenge
-> CommandAuthChallenge
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAuthChallenge CommandAuthChallenge FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAuthChallenge
x)
in
Parser CommandAuthChallenge
-> String -> Parser CommandAuthChallenge
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandAuthChallenge -> Parser CommandAuthChallenge
loop CommandAuthChallenge
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "CommandAuthChallenge"
buildMessage :: CommandAuthChallenge -> Builder
buildMessage
= \ _x :: CommandAuthChallenge
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandAuthChallenge
CommandAuthChallenge
(Maybe Text)
(Maybe Text)
-> CommandAuthChallenge -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'serverVersion") CommandAuthChallenge
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe AuthData)
CommandAuthChallenge
CommandAuthChallenge
(Maybe AuthData)
(Maybe AuthData)
-> CommandAuthChallenge -> Maybe AuthData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'challenge" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'challenge") CommandAuthChallenge
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: AuthData
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (AuthData -> ByteString) -> AuthData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
AuthData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
AuthData
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandAuthChallenge
CommandAuthChallenge
(Maybe Int32)
(Maybe Int32)
-> CommandAuthChallenge -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion") CommandAuthChallenge
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandAuthChallenge
CommandAuthChallenge
FieldSet
FieldSet
-> CommandAuthChallenge -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandAuthChallenge
CommandAuthChallenge
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAuthChallenge
_x))))
instance Control.DeepSeq.NFData CommandAuthChallenge where
rnf :: CommandAuthChallenge -> ()
rnf
= \ x__ :: CommandAuthChallenge
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthChallenge -> FieldSet
_CommandAuthChallenge'_unknownFields CommandAuthChallenge
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthChallenge -> Maybe Text
_CommandAuthChallenge'serverVersion CommandAuthChallenge
x__)
(Maybe AuthData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthChallenge -> Maybe AuthData
_CommandAuthChallenge'challenge CommandAuthChallenge
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthChallenge -> Maybe Int32
_CommandAuthChallenge'protocolVersion CommandAuthChallenge
x__) ())))
data CommandAuthResponse
= CommandAuthResponse'_constructor {CommandAuthResponse -> Maybe Text
_CommandAuthResponse'clientVersion :: !(Prelude.Maybe Data.Text.Text),
CommandAuthResponse -> Maybe AuthData
_CommandAuthResponse'response :: !(Prelude.Maybe AuthData),
CommandAuthResponse -> Maybe Int32
_CommandAuthResponse'protocolVersion :: !(Prelude.Maybe Data.Int.Int32),
CommandAuthResponse -> FieldSet
_CommandAuthResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandAuthResponse -> CommandAuthResponse -> Bool
(CommandAuthResponse -> CommandAuthResponse -> Bool)
-> (CommandAuthResponse -> CommandAuthResponse -> Bool)
-> Eq CommandAuthResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c/= :: CommandAuthResponse -> CommandAuthResponse -> Bool
== :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c== :: CommandAuthResponse -> CommandAuthResponse -> Bool
Prelude.Eq, Eq CommandAuthResponse
Eq CommandAuthResponse =>
(CommandAuthResponse -> CommandAuthResponse -> Ordering)
-> (CommandAuthResponse -> CommandAuthResponse -> Bool)
-> (CommandAuthResponse -> CommandAuthResponse -> Bool)
-> (CommandAuthResponse -> CommandAuthResponse -> Bool)
-> (CommandAuthResponse -> CommandAuthResponse -> Bool)
-> (CommandAuthResponse
-> CommandAuthResponse -> CommandAuthResponse)
-> (CommandAuthResponse
-> CommandAuthResponse -> CommandAuthResponse)
-> Ord CommandAuthResponse
CommandAuthResponse -> CommandAuthResponse -> Bool
CommandAuthResponse -> CommandAuthResponse -> Ordering
CommandAuthResponse -> CommandAuthResponse -> CommandAuthResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandAuthResponse -> CommandAuthResponse -> CommandAuthResponse
$cmin :: CommandAuthResponse -> CommandAuthResponse -> CommandAuthResponse
max :: CommandAuthResponse -> CommandAuthResponse -> CommandAuthResponse
$cmax :: CommandAuthResponse -> CommandAuthResponse -> CommandAuthResponse
>= :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c>= :: CommandAuthResponse -> CommandAuthResponse -> Bool
> :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c> :: CommandAuthResponse -> CommandAuthResponse -> Bool
<= :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c<= :: CommandAuthResponse -> CommandAuthResponse -> Bool
< :: CommandAuthResponse -> CommandAuthResponse -> Bool
$c< :: CommandAuthResponse -> CommandAuthResponse -> Bool
compare :: CommandAuthResponse -> CommandAuthResponse -> Ordering
$ccompare :: CommandAuthResponse -> CommandAuthResponse -> Ordering
$cp1Ord :: Eq CommandAuthResponse
Prelude.Ord)
instance Prelude.Show CommandAuthResponse where
showsPrec :: Int -> CommandAuthResponse -> ShowS
showsPrec _ __x :: CommandAuthResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandAuthResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandAuthResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandAuthResponse "clientVersion" Data.Text.Text where
fieldOf :: Proxy# "clientVersion"
-> (Text -> f Text) -> CommandAuthResponse -> f CommandAuthResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe Text)
-> (CommandAuthResponse -> Maybe Text -> CommandAuthResponse)
-> Lens
CommandAuthResponse CommandAuthResponse (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe Text
_CommandAuthResponse'clientVersion
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe Text
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'clientVersion :: Maybe Text
_CommandAuthResponse'clientVersion = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandAuthResponse "maybe'clientVersion" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'clientVersion"
-> (Maybe Text -> f (Maybe Text))
-> CommandAuthResponse
-> f CommandAuthResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe Text)
-> (CommandAuthResponse -> Maybe Text -> CommandAuthResponse)
-> Lens
CommandAuthResponse CommandAuthResponse (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe Text
_CommandAuthResponse'clientVersion
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe Text
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'clientVersion :: Maybe Text
_CommandAuthResponse'clientVersion = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAuthResponse "response" AuthData where
fieldOf :: Proxy# "response"
-> (AuthData -> f AuthData)
-> CommandAuthResponse
-> f CommandAuthResponse
fieldOf _
= ((Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((AuthData -> f AuthData)
-> Maybe AuthData -> f (Maybe AuthData))
-> (AuthData -> f AuthData)
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe AuthData)
-> (CommandAuthResponse -> Maybe AuthData -> CommandAuthResponse)
-> Lens
CommandAuthResponse
CommandAuthResponse
(Maybe AuthData)
(Maybe AuthData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe AuthData
_CommandAuthResponse'response
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe AuthData
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'response :: Maybe AuthData
_CommandAuthResponse'response = Maybe AuthData
y__}))
(AuthData -> Lens' (Maybe AuthData) AuthData
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens AuthData
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandAuthResponse "maybe'response" (Prelude.Maybe AuthData) where
fieldOf :: Proxy# "maybe'response"
-> (Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthResponse
-> f CommandAuthResponse
fieldOf _
= ((Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((Maybe AuthData -> f (Maybe AuthData))
-> Maybe AuthData -> f (Maybe AuthData))
-> (Maybe AuthData -> f (Maybe AuthData))
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe AuthData)
-> (CommandAuthResponse -> Maybe AuthData -> CommandAuthResponse)
-> Lens
CommandAuthResponse
CommandAuthResponse
(Maybe AuthData)
(Maybe AuthData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe AuthData
_CommandAuthResponse'response
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe AuthData
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'response :: Maybe AuthData
_CommandAuthResponse'response = Maybe AuthData
y__}))
(Maybe AuthData -> f (Maybe AuthData))
-> Maybe AuthData -> f (Maybe AuthData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandAuthResponse "protocolVersion" Data.Int.Int32 where
fieldOf :: Proxy# "protocolVersion"
-> (Int32 -> f Int32)
-> CommandAuthResponse
-> f CommandAuthResponse
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe Int32)
-> (CommandAuthResponse -> Maybe Int32 -> CommandAuthResponse)
-> Lens
CommandAuthResponse CommandAuthResponse (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe Int32
_CommandAuthResponse'protocolVersion
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe Int32
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'protocolVersion :: Maybe Int32
_CommandAuthResponse'protocolVersion = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandAuthResponse "maybe'protocolVersion" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'protocolVersion"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandAuthResponse
-> f CommandAuthResponse
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandAuthResponse -> f CommandAuthResponse)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandAuthResponse
-> f CommandAuthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandAuthResponse -> Maybe Int32)
-> (CommandAuthResponse -> Maybe Int32 -> CommandAuthResponse)
-> Lens
CommandAuthResponse CommandAuthResponse (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> Maybe Int32
_CommandAuthResponse'protocolVersion
(\ x__ :: CommandAuthResponse
x__ y__ :: Maybe Int32
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'protocolVersion :: Maybe Int32
_CommandAuthResponse'protocolVersion = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandAuthResponse where
messageName :: Proxy CommandAuthResponse -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandAuthResponse"
packedMessageDescriptor :: Proxy CommandAuthResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\DC3CommandAuthResponse\DC2%\n\
\\SOclient_version\CAN\SOH \SOH(\tR\rclientVersion\DC22\n\
\\bresponse\CAN\STX \SOH(\v2\SYN.pulsar.proto.AuthDataR\bresponse\DC2,\n\
\\DLEprotocol_version\CAN\ETX \SOH(\ENQ:\SOH0R\SIprotocolVersion"
packedFileDescriptor :: Proxy CommandAuthResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandAuthResponse)
fieldsByTag
= let
clientVersion__field_descriptor :: FieldDescriptor CommandAuthResponse
clientVersion__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandAuthResponse Text
-> FieldDescriptor CommandAuthResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"client_version"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandAuthResponse CommandAuthResponse (Maybe Text) (Maybe Text)
-> FieldAccessor CommandAuthResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'clientVersion")) ::
Data.ProtoLens.FieldDescriptor CommandAuthResponse
response__field_descriptor :: FieldDescriptor CommandAuthResponse
response__field_descriptor
= String
-> FieldTypeDescriptor AuthData
-> FieldAccessor CommandAuthResponse AuthData
-> FieldDescriptor CommandAuthResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"response"
(MessageOrGroup -> FieldTypeDescriptor AuthData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AuthData)
(Lens
CommandAuthResponse
CommandAuthResponse
(Maybe AuthData)
(Maybe AuthData)
-> FieldAccessor CommandAuthResponse AuthData
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response")) ::
Data.ProtoLens.FieldDescriptor CommandAuthResponse
protocolVersion__field_descriptor :: FieldDescriptor CommandAuthResponse
protocolVersion__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandAuthResponse Int32
-> FieldDescriptor CommandAuthResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"protocol_version"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens
CommandAuthResponse CommandAuthResponse (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandAuthResponse Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion")) ::
Data.ProtoLens.FieldDescriptor CommandAuthResponse
in
[(Tag, FieldDescriptor CommandAuthResponse)]
-> Map Tag (FieldDescriptor CommandAuthResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandAuthResponse
clientVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandAuthResponse
response__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandAuthResponse
protocolVersion__field_descriptor)]
unknownFields :: LensLike' f CommandAuthResponse FieldSet
unknownFields
= (CommandAuthResponse -> FieldSet)
-> (CommandAuthResponse -> FieldSet -> CommandAuthResponse)
-> Lens' CommandAuthResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandAuthResponse -> FieldSet
_CommandAuthResponse'_unknownFields
(\ x__ :: CommandAuthResponse
x__ y__ :: FieldSet
y__ -> CommandAuthResponse
x__ {_CommandAuthResponse'_unknownFields :: FieldSet
_CommandAuthResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandAuthResponse
defMessage
= $WCommandAuthResponse'_constructor :: Maybe Text
-> Maybe AuthData -> Maybe Int32 -> FieldSet -> CommandAuthResponse
CommandAuthResponse'_constructor
{_CommandAuthResponse'clientVersion :: Maybe Text
_CommandAuthResponse'clientVersion = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandAuthResponse'response :: Maybe AuthData
_CommandAuthResponse'response = Maybe AuthData
forall a. Maybe a
Prelude.Nothing,
_CommandAuthResponse'protocolVersion :: Maybe Int32
_CommandAuthResponse'protocolVersion = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandAuthResponse'_unknownFields :: FieldSet
_CommandAuthResponse'_unknownFields = []}
parseMessage :: Parser CommandAuthResponse
parseMessage
= let
loop ::
CommandAuthResponse
-> Data.ProtoLens.Encoding.Bytes.Parser CommandAuthResponse
loop :: CommandAuthResponse -> Parser CommandAuthResponse
loop x :: CommandAuthResponse
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
CommandAuthResponse -> Parser CommandAuthResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandAuthResponse CommandAuthResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAuthResponse
-> CommandAuthResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAuthResponse CommandAuthResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandAuthResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"client_version"
CommandAuthResponse -> Parser CommandAuthResponse
loop
(Setter CommandAuthResponse CommandAuthResponse Text Text
-> Text -> CommandAuthResponse -> CommandAuthResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"clientVersion") Text
y CommandAuthResponse
x)
18
-> do AuthData
y <- Parser AuthData -> String -> Parser AuthData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AuthData -> Parser AuthData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser AuthData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"response"
CommandAuthResponse -> Parser CommandAuthResponse
loop
(Setter CommandAuthResponse CommandAuthResponse AuthData AuthData
-> AuthData -> CommandAuthResponse -> CommandAuthResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"response") AuthData
y CommandAuthResponse
x)
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"protocol_version"
CommandAuthResponse -> Parser CommandAuthResponse
loop
(Setter CommandAuthResponse CommandAuthResponse Int32 Int32
-> Int32 -> CommandAuthResponse -> CommandAuthResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"protocolVersion") Int32
y CommandAuthResponse
x)
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandAuthResponse -> Parser CommandAuthResponse
loop
(Setter CommandAuthResponse CommandAuthResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandAuthResponse
-> CommandAuthResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandAuthResponse CommandAuthResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandAuthResponse
x)
in
Parser CommandAuthResponse -> String -> Parser CommandAuthResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandAuthResponse -> Parser CommandAuthResponse
loop CommandAuthResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "CommandAuthResponse"
buildMessage :: CommandAuthResponse -> Builder
buildMessage
= \ _x :: CommandAuthResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandAuthResponse
CommandAuthResponse
(Maybe Text)
(Maybe Text)
-> CommandAuthResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'clientVersion") CommandAuthResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe AuthData)
CommandAuthResponse
CommandAuthResponse
(Maybe AuthData)
(Maybe AuthData)
-> CommandAuthResponse -> Maybe AuthData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response") CommandAuthResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: AuthData
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (AuthData -> ByteString) -> AuthData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
AuthData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
AuthData
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandAuthResponse
CommandAuthResponse
(Maybe Int32)
(Maybe Int32)
-> CommandAuthResponse -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion") CommandAuthResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandAuthResponse CommandAuthResponse FieldSet FieldSet
-> CommandAuthResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandAuthResponse CommandAuthResponse FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandAuthResponse
_x))))
instance Control.DeepSeq.NFData CommandAuthResponse where
rnf :: CommandAuthResponse -> ()
rnf
= \ x__ :: CommandAuthResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthResponse -> FieldSet
_CommandAuthResponse'_unknownFields CommandAuthResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthResponse -> Maybe Text
_CommandAuthResponse'clientVersion CommandAuthResponse
x__)
(Maybe AuthData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthResponse -> Maybe AuthData
_CommandAuthResponse'response CommandAuthResponse
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandAuthResponse -> Maybe Int32
_CommandAuthResponse'protocolVersion CommandAuthResponse
x__) ())))
data CommandCloseConsumer
= CommandCloseConsumer'_constructor {CommandCloseConsumer -> Word64
_CommandCloseConsumer'consumerId :: !Data.Word.Word64,
CommandCloseConsumer -> Word64
_CommandCloseConsumer'requestId :: !Data.Word.Word64,
CommandCloseConsumer -> FieldSet
_CommandCloseConsumer'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandCloseConsumer -> CommandCloseConsumer -> Bool
(CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> (CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> Eq CommandCloseConsumer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c/= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
== :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c== :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
Prelude.Eq, Eq CommandCloseConsumer
Eq CommandCloseConsumer =>
(CommandCloseConsumer -> CommandCloseConsumer -> Ordering)
-> (CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> (CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> (CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> (CommandCloseConsumer -> CommandCloseConsumer -> Bool)
-> (CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer)
-> (CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer)
-> Ord CommandCloseConsumer
CommandCloseConsumer -> CommandCloseConsumer -> Bool
CommandCloseConsumer -> CommandCloseConsumer -> Ordering
CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer
$cmin :: CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer
max :: CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer
$cmax :: CommandCloseConsumer
-> CommandCloseConsumer -> CommandCloseConsumer
>= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c>= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
> :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c> :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
<= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c<= :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
< :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
$c< :: CommandCloseConsumer -> CommandCloseConsumer -> Bool
compare :: CommandCloseConsumer -> CommandCloseConsumer -> Ordering
$ccompare :: CommandCloseConsumer -> CommandCloseConsumer -> Ordering
$cp1Ord :: Eq CommandCloseConsumer
Prelude.Ord)
instance Prelude.Show CommandCloseConsumer where
showsPrec :: Int -> CommandCloseConsumer -> ShowS
showsPrec _ __x :: CommandCloseConsumer
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandCloseConsumer -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandCloseConsumer
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandCloseConsumer "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandCloseConsumer
-> f CommandCloseConsumer
fieldOf _
= ((Word64 -> f Word64)
-> CommandCloseConsumer -> f CommandCloseConsumer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandCloseConsumer
-> f CommandCloseConsumer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandCloseConsumer -> Word64)
-> (CommandCloseConsumer -> Word64 -> CommandCloseConsumer)
-> Lens CommandCloseConsumer CommandCloseConsumer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseConsumer -> Word64
_CommandCloseConsumer'consumerId
(\ x__ :: CommandCloseConsumer
x__ y__ :: Word64
y__ -> CommandCloseConsumer
x__ {_CommandCloseConsumer'consumerId :: Word64
_CommandCloseConsumer'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandCloseConsumer "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandCloseConsumer
-> f CommandCloseConsumer
fieldOf _
= ((Word64 -> f Word64)
-> CommandCloseConsumer -> f CommandCloseConsumer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandCloseConsumer
-> f CommandCloseConsumer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandCloseConsumer -> Word64)
-> (CommandCloseConsumer -> Word64 -> CommandCloseConsumer)
-> Lens CommandCloseConsumer CommandCloseConsumer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseConsumer -> Word64
_CommandCloseConsumer'requestId
(\ x__ :: CommandCloseConsumer
x__ y__ :: Word64
y__ -> CommandCloseConsumer
x__ {_CommandCloseConsumer'requestId :: Word64
_CommandCloseConsumer'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandCloseConsumer where
messageName :: Proxy CommandCloseConsumer -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandCloseConsumer"
packedMessageDescriptor :: Proxy CommandCloseConsumer -> ByteString
packedMessageDescriptor _
= "\n\
\\DC4CommandCloseConsumer\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId"
packedFileDescriptor :: Proxy CommandCloseConsumer -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandCloseConsumer)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandCloseConsumer
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandCloseConsumer Word64
-> FieldDescriptor CommandCloseConsumer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> FieldAccessor CommandCloseConsumer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandCloseConsumer
requestId__field_descriptor :: FieldDescriptor CommandCloseConsumer
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandCloseConsumer Word64
-> FieldDescriptor CommandCloseConsumer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> FieldAccessor CommandCloseConsumer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandCloseConsumer
in
[(Tag, FieldDescriptor CommandCloseConsumer)]
-> Map Tag (FieldDescriptor CommandCloseConsumer)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandCloseConsumer
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandCloseConsumer
requestId__field_descriptor)]
unknownFields :: LensLike' f CommandCloseConsumer FieldSet
unknownFields
= (CommandCloseConsumer -> FieldSet)
-> (CommandCloseConsumer -> FieldSet -> CommandCloseConsumer)
-> Lens' CommandCloseConsumer FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseConsumer -> FieldSet
_CommandCloseConsumer'_unknownFields
(\ x__ :: CommandCloseConsumer
x__ y__ :: FieldSet
y__ -> CommandCloseConsumer
x__ {_CommandCloseConsumer'_unknownFields :: FieldSet
_CommandCloseConsumer'_unknownFields = FieldSet
y__})
defMessage :: CommandCloseConsumer
defMessage
= $WCommandCloseConsumer'_constructor :: Word64 -> Word64 -> FieldSet -> CommandCloseConsumer
CommandCloseConsumer'_constructor
{_CommandCloseConsumer'consumerId :: Word64
_CommandCloseConsumer'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandCloseConsumer'requestId :: Word64
_CommandCloseConsumer'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandCloseConsumer'_unknownFields :: FieldSet
_CommandCloseConsumer'_unknownFields = []}
parseMessage :: Parser CommandCloseConsumer
parseMessage
= let
loop ::
CommandCloseConsumer
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandCloseConsumer
loop :: CommandCloseConsumer -> Bool -> Bool -> Parser CommandCloseConsumer
loop x :: CommandCloseConsumer
x required'consumerId :: Bool
required'consumerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandCloseConsumer -> Parser CommandCloseConsumer
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandCloseConsumer CommandCloseConsumer FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandCloseConsumer
-> CommandCloseConsumer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandCloseConsumer CommandCloseConsumer FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandCloseConsumer
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandCloseConsumer -> Bool -> Bool -> Parser CommandCloseConsumer
loop
(Setter CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> Word64 -> CommandCloseConsumer -> CommandCloseConsumer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandCloseConsumer
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandCloseConsumer -> Bool -> Bool -> Parser CommandCloseConsumer
loop
(Setter CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> Word64 -> CommandCloseConsumer -> CommandCloseConsumer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandCloseConsumer
x)
Bool
required'consumerId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandCloseConsumer -> Bool -> Bool -> Parser CommandCloseConsumer
loop
(Setter CommandCloseConsumer CommandCloseConsumer FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandCloseConsumer
-> CommandCloseConsumer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandCloseConsumer CommandCloseConsumer FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandCloseConsumer
x)
Bool
required'consumerId
Bool
required'requestId
in
Parser CommandCloseConsumer
-> String -> Parser CommandCloseConsumer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandCloseConsumer -> Bool -> Bool -> Parser CommandCloseConsumer
loop CommandCloseConsumer
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandCloseConsumer"
buildMessage :: CommandCloseConsumer -> Builder
buildMessage
= \ _x :: CommandCloseConsumer
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> CommandCloseConsumer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandCloseConsumer
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandCloseConsumer CommandCloseConsumer Word64 Word64
-> CommandCloseConsumer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandCloseConsumer
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandCloseConsumer
CommandCloseConsumer
FieldSet
FieldSet
-> CommandCloseConsumer -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandCloseConsumer
CommandCloseConsumer
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandCloseConsumer
_x)))
instance Control.DeepSeq.NFData CommandCloseConsumer where
rnf :: CommandCloseConsumer -> ()
rnf
= \ x__ :: CommandCloseConsumer
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandCloseConsumer -> FieldSet
_CommandCloseConsumer'_unknownFields CommandCloseConsumer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandCloseConsumer -> Word64
_CommandCloseConsumer'consumerId CommandCloseConsumer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandCloseConsumer -> Word64
_CommandCloseConsumer'requestId CommandCloseConsumer
x__) ()))
data CommandCloseProducer
= CommandCloseProducer'_constructor {CommandCloseProducer -> Word64
_CommandCloseProducer'producerId :: !Data.Word.Word64,
CommandCloseProducer -> Word64
_CommandCloseProducer'requestId :: !Data.Word.Word64,
CommandCloseProducer -> FieldSet
_CommandCloseProducer'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandCloseProducer -> CommandCloseProducer -> Bool
(CommandCloseProducer -> CommandCloseProducer -> Bool)
-> (CommandCloseProducer -> CommandCloseProducer -> Bool)
-> Eq CommandCloseProducer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c/= :: CommandCloseProducer -> CommandCloseProducer -> Bool
== :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c== :: CommandCloseProducer -> CommandCloseProducer -> Bool
Prelude.Eq, Eq CommandCloseProducer
Eq CommandCloseProducer =>
(CommandCloseProducer -> CommandCloseProducer -> Ordering)
-> (CommandCloseProducer -> CommandCloseProducer -> Bool)
-> (CommandCloseProducer -> CommandCloseProducer -> Bool)
-> (CommandCloseProducer -> CommandCloseProducer -> Bool)
-> (CommandCloseProducer -> CommandCloseProducer -> Bool)
-> (CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer)
-> (CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer)
-> Ord CommandCloseProducer
CommandCloseProducer -> CommandCloseProducer -> Bool
CommandCloseProducer -> CommandCloseProducer -> Ordering
CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer
$cmin :: CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer
max :: CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer
$cmax :: CommandCloseProducer
-> CommandCloseProducer -> CommandCloseProducer
>= :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c>= :: CommandCloseProducer -> CommandCloseProducer -> Bool
> :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c> :: CommandCloseProducer -> CommandCloseProducer -> Bool
<= :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c<= :: CommandCloseProducer -> CommandCloseProducer -> Bool
< :: CommandCloseProducer -> CommandCloseProducer -> Bool
$c< :: CommandCloseProducer -> CommandCloseProducer -> Bool
compare :: CommandCloseProducer -> CommandCloseProducer -> Ordering
$ccompare :: CommandCloseProducer -> CommandCloseProducer -> Ordering
$cp1Ord :: Eq CommandCloseProducer
Prelude.Ord)
instance Prelude.Show CommandCloseProducer where
showsPrec :: Int -> CommandCloseProducer -> ShowS
showsPrec _ __x :: CommandCloseProducer
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandCloseProducer -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandCloseProducer
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandCloseProducer "producerId" Data.Word.Word64 where
fieldOf :: Proxy# "producerId"
-> (Word64 -> f Word64)
-> CommandCloseProducer
-> f CommandCloseProducer
fieldOf _
= ((Word64 -> f Word64)
-> CommandCloseProducer -> f CommandCloseProducer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandCloseProducer
-> f CommandCloseProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandCloseProducer -> Word64)
-> (CommandCloseProducer -> Word64 -> CommandCloseProducer)
-> Lens CommandCloseProducer CommandCloseProducer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseProducer -> Word64
_CommandCloseProducer'producerId
(\ x__ :: CommandCloseProducer
x__ y__ :: Word64
y__ -> CommandCloseProducer
x__ {_CommandCloseProducer'producerId :: Word64
_CommandCloseProducer'producerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandCloseProducer "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandCloseProducer
-> f CommandCloseProducer
fieldOf _
= ((Word64 -> f Word64)
-> CommandCloseProducer -> f CommandCloseProducer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandCloseProducer
-> f CommandCloseProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandCloseProducer -> Word64)
-> (CommandCloseProducer -> Word64 -> CommandCloseProducer)
-> Lens CommandCloseProducer CommandCloseProducer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseProducer -> Word64
_CommandCloseProducer'requestId
(\ x__ :: CommandCloseProducer
x__ y__ :: Word64
y__ -> CommandCloseProducer
x__ {_CommandCloseProducer'requestId :: Word64
_CommandCloseProducer'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandCloseProducer where
messageName :: Proxy CommandCloseProducer -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandCloseProducer"
packedMessageDescriptor :: Proxy CommandCloseProducer -> ByteString
packedMessageDescriptor _
= "\n\
\\DC4CommandCloseProducer\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId"
packedFileDescriptor :: Proxy CommandCloseProducer -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandCloseProducer)
fieldsByTag
= let
producerId__field_descriptor :: FieldDescriptor CommandCloseProducer
producerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandCloseProducer Word64
-> FieldDescriptor CommandCloseProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandCloseProducer CommandCloseProducer Word64 Word64
-> FieldAccessor CommandCloseProducer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId")) ::
Data.ProtoLens.FieldDescriptor CommandCloseProducer
requestId__field_descriptor :: FieldDescriptor CommandCloseProducer
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandCloseProducer Word64
-> FieldDescriptor CommandCloseProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandCloseProducer CommandCloseProducer Word64 Word64
-> FieldAccessor CommandCloseProducer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandCloseProducer
in
[(Tag, FieldDescriptor CommandCloseProducer)]
-> Map Tag (FieldDescriptor CommandCloseProducer)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandCloseProducer
producerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandCloseProducer
requestId__field_descriptor)]
unknownFields :: LensLike' f CommandCloseProducer FieldSet
unknownFields
= (CommandCloseProducer -> FieldSet)
-> (CommandCloseProducer -> FieldSet -> CommandCloseProducer)
-> Lens' CommandCloseProducer FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandCloseProducer -> FieldSet
_CommandCloseProducer'_unknownFields
(\ x__ :: CommandCloseProducer
x__ y__ :: FieldSet
y__ -> CommandCloseProducer
x__ {_CommandCloseProducer'_unknownFields :: FieldSet
_CommandCloseProducer'_unknownFields = FieldSet
y__})
defMessage :: CommandCloseProducer
defMessage
= $WCommandCloseProducer'_constructor :: Word64 -> Word64 -> FieldSet -> CommandCloseProducer
CommandCloseProducer'_constructor
{_CommandCloseProducer'producerId :: Word64
_CommandCloseProducer'producerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandCloseProducer'requestId :: Word64
_CommandCloseProducer'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandCloseProducer'_unknownFields :: FieldSet
_CommandCloseProducer'_unknownFields = []}
parseMessage :: Parser CommandCloseProducer
parseMessage
= let
loop ::
CommandCloseProducer
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandCloseProducer
loop :: CommandCloseProducer -> Bool -> Bool -> Parser CommandCloseProducer
loop x :: CommandCloseProducer
x required'producerId :: Bool
required'producerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'producerId then (:) "producer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandCloseProducer -> Parser CommandCloseProducer
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandCloseProducer CommandCloseProducer FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandCloseProducer
-> CommandCloseProducer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandCloseProducer CommandCloseProducer FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandCloseProducer
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "producer_id"
CommandCloseProducer -> Bool -> Bool -> Parser CommandCloseProducer
loop
(Setter CommandCloseProducer CommandCloseProducer Word64 Word64
-> Word64 -> CommandCloseProducer -> CommandCloseProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") Word64
y CommandCloseProducer
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandCloseProducer -> Bool -> Bool -> Parser CommandCloseProducer
loop
(Setter CommandCloseProducer CommandCloseProducer Word64 Word64
-> Word64 -> CommandCloseProducer -> CommandCloseProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandCloseProducer
x)
Bool
required'producerId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandCloseProducer -> Bool -> Bool -> Parser CommandCloseProducer
loop
(Setter CommandCloseProducer CommandCloseProducer FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandCloseProducer
-> CommandCloseProducer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandCloseProducer CommandCloseProducer FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandCloseProducer
x)
Bool
required'producerId
Bool
required'requestId
in
Parser CommandCloseProducer
-> String -> Parser CommandCloseProducer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandCloseProducer -> Bool -> Bool -> Parser CommandCloseProducer
loop CommandCloseProducer
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandCloseProducer"
buildMessage :: CommandCloseProducer -> Builder
buildMessage
= \ _x :: CommandCloseProducer
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandCloseProducer CommandCloseProducer Word64 Word64
-> CommandCloseProducer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") CommandCloseProducer
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandCloseProducer CommandCloseProducer Word64 Word64
-> CommandCloseProducer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandCloseProducer
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandCloseProducer
CommandCloseProducer
FieldSet
FieldSet
-> CommandCloseProducer -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandCloseProducer
CommandCloseProducer
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandCloseProducer
_x)))
instance Control.DeepSeq.NFData CommandCloseProducer where
rnf :: CommandCloseProducer -> ()
rnf
= \ x__ :: CommandCloseProducer
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandCloseProducer -> FieldSet
_CommandCloseProducer'_unknownFields CommandCloseProducer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandCloseProducer -> Word64
_CommandCloseProducer'producerId CommandCloseProducer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandCloseProducer -> Word64
_CommandCloseProducer'requestId CommandCloseProducer
x__) ()))
data CommandConnect
= CommandConnect'_constructor {CommandConnect -> Text
_CommandConnect'clientVersion :: !Data.Text.Text,
CommandConnect -> Maybe AuthMethod
_CommandConnect'authMethod :: !(Prelude.Maybe AuthMethod),
CommandConnect -> Maybe Text
_CommandConnect'authMethodName :: !(Prelude.Maybe Data.Text.Text),
CommandConnect -> Maybe ByteString
_CommandConnect'authData :: !(Prelude.Maybe Data.ByteString.ByteString),
CommandConnect -> Maybe Int32
_CommandConnect'protocolVersion :: !(Prelude.Maybe Data.Int.Int32),
CommandConnect -> Maybe Text
_CommandConnect'proxyToBrokerUrl :: !(Prelude.Maybe Data.Text.Text),
CommandConnect -> Maybe Text
_CommandConnect'originalPrincipal :: !(Prelude.Maybe Data.Text.Text),
CommandConnect -> Maybe Text
_CommandConnect'originalAuthData :: !(Prelude.Maybe Data.Text.Text),
CommandConnect -> Maybe Text
_CommandConnect'originalAuthMethod :: !(Prelude.Maybe Data.Text.Text),
CommandConnect -> Maybe FeatureFlags
_CommandConnect'featureFlags :: !(Prelude.Maybe FeatureFlags),
CommandConnect -> FieldSet
_CommandConnect'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandConnect -> CommandConnect -> Bool
(CommandConnect -> CommandConnect -> Bool)
-> (CommandConnect -> CommandConnect -> Bool) -> Eq CommandConnect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandConnect -> CommandConnect -> Bool
$c/= :: CommandConnect -> CommandConnect -> Bool
== :: CommandConnect -> CommandConnect -> Bool
$c== :: CommandConnect -> CommandConnect -> Bool
Prelude.Eq, Eq CommandConnect
Eq CommandConnect =>
(CommandConnect -> CommandConnect -> Ordering)
-> (CommandConnect -> CommandConnect -> Bool)
-> (CommandConnect -> CommandConnect -> Bool)
-> (CommandConnect -> CommandConnect -> Bool)
-> (CommandConnect -> CommandConnect -> Bool)
-> (CommandConnect -> CommandConnect -> CommandConnect)
-> (CommandConnect -> CommandConnect -> CommandConnect)
-> Ord CommandConnect
CommandConnect -> CommandConnect -> Bool
CommandConnect -> CommandConnect -> Ordering
CommandConnect -> CommandConnect -> CommandConnect
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandConnect -> CommandConnect -> CommandConnect
$cmin :: CommandConnect -> CommandConnect -> CommandConnect
max :: CommandConnect -> CommandConnect -> CommandConnect
$cmax :: CommandConnect -> CommandConnect -> CommandConnect
>= :: CommandConnect -> CommandConnect -> Bool
$c>= :: CommandConnect -> CommandConnect -> Bool
> :: CommandConnect -> CommandConnect -> Bool
$c> :: CommandConnect -> CommandConnect -> Bool
<= :: CommandConnect -> CommandConnect -> Bool
$c<= :: CommandConnect -> CommandConnect -> Bool
< :: CommandConnect -> CommandConnect -> Bool
$c< :: CommandConnect -> CommandConnect -> Bool
compare :: CommandConnect -> CommandConnect -> Ordering
$ccompare :: CommandConnect -> CommandConnect -> Ordering
$cp1Ord :: Eq CommandConnect
Prelude.Ord)
instance Prelude.Show CommandConnect where
showsPrec :: Int -> CommandConnect -> ShowS
showsPrec _ __x :: CommandConnect
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandConnect -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandConnect
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandConnect "clientVersion" Data.Text.Text where
fieldOf :: Proxy# "clientVersion"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Text -> f Text) -> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Text)
-> (CommandConnect -> Text -> CommandConnect)
-> Lens CommandConnect CommandConnect Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Text
_CommandConnect'clientVersion
(\ x__ :: CommandConnect
x__ y__ :: Text
y__ -> CommandConnect
x__ {_CommandConnect'clientVersion :: Text
_CommandConnect'clientVersion = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "authMethod" AuthMethod where
fieldOf :: Proxy# "authMethod"
-> (AuthMethod -> f AuthMethod)
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe AuthMethod -> f (Maybe AuthMethod))
-> CommandConnect -> f CommandConnect)
-> ((AuthMethod -> f AuthMethod)
-> Maybe AuthMethod -> f (Maybe AuthMethod))
-> (AuthMethod -> f AuthMethod)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe AuthMethod)
-> (CommandConnect -> Maybe AuthMethod -> CommandConnect)
-> Lens
CommandConnect CommandConnect (Maybe AuthMethod) (Maybe AuthMethod)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe AuthMethod
_CommandConnect'authMethod
(\ x__ :: CommandConnect
x__ y__ :: Maybe AuthMethod
y__ -> CommandConnect
x__ {_CommandConnect'authMethod :: Maybe AuthMethod
_CommandConnect'authMethod = Maybe AuthMethod
y__}))
(AuthMethod -> Lens' (Maybe AuthMethod) AuthMethod
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens AuthMethod
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'authMethod" (Prelude.Maybe AuthMethod) where
fieldOf :: Proxy# "maybe'authMethod"
-> (Maybe AuthMethod -> f (Maybe AuthMethod))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe AuthMethod -> f (Maybe AuthMethod))
-> CommandConnect -> f CommandConnect)
-> ((Maybe AuthMethod -> f (Maybe AuthMethod))
-> Maybe AuthMethod -> f (Maybe AuthMethod))
-> (Maybe AuthMethod -> f (Maybe AuthMethod))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe AuthMethod)
-> (CommandConnect -> Maybe AuthMethod -> CommandConnect)
-> Lens
CommandConnect CommandConnect (Maybe AuthMethod) (Maybe AuthMethod)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe AuthMethod
_CommandConnect'authMethod
(\ x__ :: CommandConnect
x__ y__ :: Maybe AuthMethod
y__ -> CommandConnect
x__ {_CommandConnect'authMethod :: Maybe AuthMethod
_CommandConnect'authMethod = Maybe AuthMethod
y__}))
(Maybe AuthMethod -> f (Maybe AuthMethod))
-> Maybe AuthMethod -> f (Maybe AuthMethod)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "authMethodName" Data.Text.Text where
fieldOf :: Proxy# "authMethodName"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'authMethodName
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'authMethodName :: Maybe Text
_CommandConnect'authMethodName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'authMethodName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'authMethodName"
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'authMethodName
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'authMethodName :: Maybe Text
_CommandConnect'authMethodName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "authData" Data.ByteString.ByteString where
fieldOf :: Proxy# "authData"
-> (ByteString -> f ByteString)
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandConnect -> f CommandConnect)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe ByteString)
-> (CommandConnect -> Maybe ByteString -> CommandConnect)
-> Lens
CommandConnect CommandConnect (Maybe ByteString) (Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe ByteString
_CommandConnect'authData
(\ x__ :: CommandConnect
x__ y__ :: Maybe ByteString
y__ -> CommandConnect
x__ {_CommandConnect'authData :: Maybe ByteString
_CommandConnect'authData = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'authData" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'authData"
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandConnect -> f CommandConnect)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe ByteString)
-> (CommandConnect -> Maybe ByteString -> CommandConnect)
-> Lens
CommandConnect CommandConnect (Maybe ByteString) (Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe ByteString
_CommandConnect'authData
(\ x__ :: CommandConnect
x__ y__ :: Maybe ByteString
y__ -> CommandConnect
x__ {_CommandConnect'authData :: Maybe ByteString
_CommandConnect'authData = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "protocolVersion" Data.Int.Int32 where
fieldOf :: Proxy# "protocolVersion"
-> (Int32 -> f Int32) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnect -> f CommandConnect)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Int32)
-> (CommandConnect -> Maybe Int32 -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Int32
_CommandConnect'protocolVersion
(\ x__ :: CommandConnect
x__ y__ :: Maybe Int32
y__ -> CommandConnect
x__ {_CommandConnect'protocolVersion :: Maybe Int32
_CommandConnect'protocolVersion = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'protocolVersion" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'protocolVersion"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Int32)
-> (CommandConnect -> Maybe Int32 -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Int32
_CommandConnect'protocolVersion
(\ x__ :: CommandConnect
x__ y__ :: Maybe Int32
y__ -> CommandConnect
x__ {_CommandConnect'protocolVersion :: Maybe Int32
_CommandConnect'protocolVersion = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "proxyToBrokerUrl" Data.Text.Text where
fieldOf :: Proxy# "proxyToBrokerUrl"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'proxyToBrokerUrl
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'proxyToBrokerUrl :: Maybe Text
_CommandConnect'proxyToBrokerUrl = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'proxyToBrokerUrl" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'proxyToBrokerUrl"
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'proxyToBrokerUrl
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'proxyToBrokerUrl :: Maybe Text
_CommandConnect'proxyToBrokerUrl = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "originalPrincipal" Data.Text.Text where
fieldOf :: Proxy# "originalPrincipal"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalPrincipal
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalPrincipal :: Maybe Text
_CommandConnect'originalPrincipal = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'originalPrincipal" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalPrincipal"
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalPrincipal
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalPrincipal :: Maybe Text
_CommandConnect'originalPrincipal = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "originalAuthData" Data.Text.Text where
fieldOf :: Proxy# "originalAuthData"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalAuthData
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalAuthData :: Maybe Text
_CommandConnect'originalAuthData = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'originalAuthData" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthData"
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalAuthData
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalAuthData :: Maybe Text
_CommandConnect'originalAuthData = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "originalAuthMethod" Data.Text.Text where
fieldOf :: Proxy# "originalAuthMethod"
-> (Text -> f Text) -> CommandConnect -> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalAuthMethod
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalAuthMethod :: Maybe Text
_CommandConnect'originalAuthMethod = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'originalAuthMethod" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthMethod"
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConnect -> f CommandConnect)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe Text)
-> (CommandConnect -> Maybe Text -> CommandConnect)
-> Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe Text
_CommandConnect'originalAuthMethod
(\ x__ :: CommandConnect
x__ y__ :: Maybe Text
y__ -> CommandConnect
x__ {_CommandConnect'originalAuthMethod :: Maybe Text
_CommandConnect'originalAuthMethod = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnect "featureFlags" FeatureFlags where
fieldOf :: Proxy# "featureFlags"
-> (FeatureFlags -> f FeatureFlags)
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> CommandConnect -> f CommandConnect)
-> ((FeatureFlags -> f FeatureFlags)
-> Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> (FeatureFlags -> f FeatureFlags)
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe FeatureFlags)
-> (CommandConnect -> Maybe FeatureFlags -> CommandConnect)
-> Lens
CommandConnect
CommandConnect
(Maybe FeatureFlags)
(Maybe FeatureFlags)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe FeatureFlags
_CommandConnect'featureFlags
(\ x__ :: CommandConnect
x__ y__ :: Maybe FeatureFlags
y__ -> CommandConnect
x__ {_CommandConnect'featureFlags :: Maybe FeatureFlags
_CommandConnect'featureFlags = Maybe FeatureFlags
y__}))
(FeatureFlags -> Lens' (Maybe FeatureFlags) FeatureFlags
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens FeatureFlags
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandConnect "maybe'featureFlags" (Prelude.Maybe FeatureFlags) where
fieldOf :: Proxy# "maybe'featureFlags"
-> (Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> CommandConnect
-> f CommandConnect
fieldOf _
= ((Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> CommandConnect -> f CommandConnect)
-> ((Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> (Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> CommandConnect
-> f CommandConnect
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnect -> Maybe FeatureFlags)
-> (CommandConnect -> Maybe FeatureFlags -> CommandConnect)
-> Lens
CommandConnect
CommandConnect
(Maybe FeatureFlags)
(Maybe FeatureFlags)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> Maybe FeatureFlags
_CommandConnect'featureFlags
(\ x__ :: CommandConnect
x__ y__ :: Maybe FeatureFlags
y__ -> CommandConnect
x__ {_CommandConnect'featureFlags :: Maybe FeatureFlags
_CommandConnect'featureFlags = Maybe FeatureFlags
y__}))
(Maybe FeatureFlags -> f (Maybe FeatureFlags))
-> Maybe FeatureFlags -> f (Maybe FeatureFlags)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandConnect where
messageName :: Proxy CommandConnect -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandConnect"
packedMessageDescriptor :: Proxy CommandConnect -> ByteString
packedMessageDescriptor _
= "\n\
\\SOCommandConnect\DC2%\n\
\\SOclient_version\CAN\SOH \STX(\tR\rclientVersion\DC29\n\
\\vauth_method\CAN\STX \SOH(\SO2\CAN.pulsar.proto.AuthMethodR\n\
\authMethod\DC2(\n\
\\DLEauth_method_name\CAN\ENQ \SOH(\tR\SOauthMethodName\DC2\ESC\n\
\\tauth_data\CAN\ETX \SOH(\fR\bauthData\DC2,\n\
\\DLEprotocol_version\CAN\EOT \SOH(\ENQ:\SOH0R\SIprotocolVersion\DC2-\n\
\\DC3proxy_to_broker_url\CAN\ACK \SOH(\tR\DLEproxyToBrokerUrl\DC2-\n\
\\DC2original_principal\CAN\a \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\b \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\t \SOH(\tR\DC2originalAuthMethod\DC2?\n\
\\rfeature_flags\CAN\n\
\ \SOH(\v2\SUB.pulsar.proto.FeatureFlagsR\ffeatureFlags"
packedFileDescriptor :: Proxy CommandConnect -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandConnect)
fieldsByTag
= let
clientVersion__field_descriptor :: FieldDescriptor CommandConnect
clientVersion__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"client_version"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandConnect CommandConnect Text Text
-> FieldAccessor CommandConnect Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"clientVersion")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
authMethod__field_descriptor :: FieldDescriptor CommandConnect
authMethod__field_descriptor
= String
-> FieldTypeDescriptor AuthMethod
-> FieldAccessor CommandConnect AuthMethod
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"auth_method"
(ScalarField AuthMethod -> FieldTypeDescriptor AuthMethod
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField AuthMethod
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor AuthMethod)
(Lens
CommandConnect CommandConnect (Maybe AuthMethod) (Maybe AuthMethod)
-> FieldAccessor CommandConnect AuthMethod
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethod")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
authMethodName__field_descriptor :: FieldDescriptor CommandConnect
authMethodName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"auth_method_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
-> FieldAccessor CommandConnect Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethodName")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
authData__field_descriptor :: FieldDescriptor CommandConnect
authData__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor CommandConnect ByteString
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"auth_data"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
CommandConnect CommandConnect (Maybe ByteString) (Maybe ByteString)
-> FieldAccessor CommandConnect ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authData")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
protocolVersion__field_descriptor :: FieldDescriptor CommandConnect
protocolVersion__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandConnect Int32
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"protocol_version"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens CommandConnect CommandConnect (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandConnect Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
proxyToBrokerUrl__field_descriptor :: FieldDescriptor CommandConnect
proxyToBrokerUrl__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"proxy_to_broker_url"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
-> FieldAccessor CommandConnect Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'proxyToBrokerUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'proxyToBrokerUrl")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
originalPrincipal__field_descriptor :: FieldDescriptor CommandConnect
originalPrincipal__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_principal"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
-> FieldAccessor CommandConnect Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
originalAuthData__field_descriptor :: FieldDescriptor CommandConnect
originalAuthData__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_data"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
-> FieldAccessor CommandConnect Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
originalAuthMethod__field_descriptor :: FieldDescriptor CommandConnect
originalAuthMethod__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnect Text
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_method"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandConnect CommandConnect (Maybe Text) (Maybe Text)
-> FieldAccessor CommandConnect Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
featureFlags__field_descriptor :: FieldDescriptor CommandConnect
featureFlags__field_descriptor
= String
-> FieldTypeDescriptor FeatureFlags
-> FieldAccessor CommandConnect FeatureFlags
-> FieldDescriptor CommandConnect
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"feature_flags"
(MessageOrGroup -> FieldTypeDescriptor FeatureFlags
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor FeatureFlags)
(Lens
CommandConnect
CommandConnect
(Maybe FeatureFlags)
(Maybe FeatureFlags)
-> FieldAccessor CommandConnect FeatureFlags
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'featureFlags" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'featureFlags")) ::
Data.ProtoLens.FieldDescriptor CommandConnect
in
[(Tag, FieldDescriptor CommandConnect)]
-> Map Tag (FieldDescriptor CommandConnect)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandConnect
clientVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandConnect
authMethod__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandConnect
authMethodName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandConnect
authData__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandConnect
protocolVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandConnect
proxyToBrokerUrl__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandConnect
originalPrincipal__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor CommandConnect
originalAuthData__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor CommandConnect
originalAuthMethod__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 10, FieldDescriptor CommandConnect
featureFlags__field_descriptor)]
unknownFields :: LensLike' f CommandConnect FieldSet
unknownFields
= (CommandConnect -> FieldSet)
-> (CommandConnect -> FieldSet -> CommandConnect)
-> Lens' CommandConnect FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnect -> FieldSet
_CommandConnect'_unknownFields
(\ x__ :: CommandConnect
x__ y__ :: FieldSet
y__ -> CommandConnect
x__ {_CommandConnect'_unknownFields :: FieldSet
_CommandConnect'_unknownFields = FieldSet
y__})
defMessage :: CommandConnect
defMessage
= $WCommandConnect'_constructor :: Text
-> Maybe AuthMethod
-> Maybe Text
-> Maybe ByteString
-> Maybe Int32
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe FeatureFlags
-> FieldSet
-> CommandConnect
CommandConnect'_constructor
{_CommandConnect'clientVersion :: Text
_CommandConnect'clientVersion = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandConnect'authMethod :: Maybe AuthMethod
_CommandConnect'authMethod = Maybe AuthMethod
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'authMethodName :: Maybe Text
_CommandConnect'authMethodName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'authData :: Maybe ByteString
_CommandConnect'authData = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'protocolVersion :: Maybe Int32
_CommandConnect'protocolVersion = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'proxyToBrokerUrl :: Maybe Text
_CommandConnect'proxyToBrokerUrl = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'originalPrincipal :: Maybe Text
_CommandConnect'originalPrincipal = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'originalAuthData :: Maybe Text
_CommandConnect'originalAuthData = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'originalAuthMethod :: Maybe Text
_CommandConnect'originalAuthMethod = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'featureFlags :: Maybe FeatureFlags
_CommandConnect'featureFlags = Maybe FeatureFlags
forall a. Maybe a
Prelude.Nothing,
_CommandConnect'_unknownFields :: FieldSet
_CommandConnect'_unknownFields = []}
parseMessage :: Parser CommandConnect
parseMessage
= let
loop ::
CommandConnect
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandConnect
loop :: CommandConnect -> Bool -> Parser CommandConnect
loop x :: CommandConnect
x required'clientVersion :: Bool
required'clientVersion
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'clientVersion then
(:) "client_version"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandConnect -> Parser CommandConnect
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandConnect CommandConnect FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConnect CommandConnect FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandConnect
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"client_version"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"clientVersion") Text
y CommandConnect
x)
Bool
Prelude.False
16
-> do AuthMethod
y <- Parser AuthMethod -> String -> Parser AuthMethod
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> AuthMethod) -> Parser Int -> Parser AuthMethod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> AuthMethod
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"auth_method"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect AuthMethod AuthMethod
-> AuthMethod -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "authMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authMethod") AuthMethod
y CommandConnect
x)
Bool
required'clientVersion
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"auth_method_name"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authMethodName") Text
y CommandConnect
x)
Bool
required'clientVersion
26
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"auth_data"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect ByteString ByteString
-> ByteString -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authData") ByteString
y CommandConnect
x)
Bool
required'clientVersion
32
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"protocol_version"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Int32 Int32
-> Int32 -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"protocolVersion") Int32
y CommandConnect
x)
Bool
required'clientVersion
50
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"proxy_to_broker_url"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "proxyToBrokerUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"proxyToBrokerUrl") Text
y CommandConnect
x)
Bool
required'clientVersion
58
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_principal"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalPrincipal") Text
y CommandConnect
x)
Bool
required'clientVersion
66
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_data"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthData") Text
y CommandConnect
x)
Bool
required'clientVersion
74
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_method"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect Text Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthMethod") Text
y CommandConnect
x)
Bool
required'clientVersion
82
-> do FeatureFlags
y <- Parser FeatureFlags -> String -> Parser FeatureFlags
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser FeatureFlags -> Parser FeatureFlags
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser FeatureFlags
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"feature_flags"
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect FeatureFlags FeatureFlags
-> FeatureFlags -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "featureFlags" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"featureFlags") FeatureFlags
y CommandConnect
x)
Bool
required'clientVersion
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandConnect -> Bool -> Parser CommandConnect
loop
(Setter CommandConnect CommandConnect FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandConnect -> CommandConnect
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConnect CommandConnect FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandConnect
x)
Bool
required'clientVersion
in
Parser CommandConnect -> String -> Parser CommandConnect
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandConnect -> Bool -> Parser CommandConnect
loop CommandConnect
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "CommandConnect"
buildMessage :: CommandConnect -> Builder
buildMessage
= \ _x :: CommandConnect
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandConnect CommandConnect Text Text
-> CommandConnect -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "clientVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"clientVersion") CommandConnect
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe AuthMethod)
CommandConnect
CommandConnect
(Maybe AuthMethod)
(Maybe AuthMethod)
-> CommandConnect -> Maybe AuthMethod
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethod") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: AuthMethod
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder) -> (AuthMethod -> Int) -> AuthMethod -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
AuthMethod -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
AuthMethod
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConnect
CommandConnect
(Maybe Text)
(Maybe Text)
-> CommandConnect -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authMethodName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authMethodName") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
CommandConnect
CommandConnect
(Maybe ByteString)
(Maybe ByteString)
-> CommandConnect -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'authData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authData") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandConnect
CommandConnect
(Maybe Int32)
(Maybe Int32)
-> CommandConnect -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConnect
CommandConnect
(Maybe Text)
(Maybe Text)
-> CommandConnect -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'proxyToBrokerUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'proxyToBrokerUrl") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConnect
CommandConnect
(Maybe Text)
(Maybe Text)
-> CommandConnect -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConnect
CommandConnect
(Maybe Text)
(Maybe Text)
-> CommandConnect -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 66)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConnect
CommandConnect
(Maybe Text)
(Maybe Text)
-> CommandConnect -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod")
CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 74)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe FeatureFlags)
CommandConnect
CommandConnect
(Maybe FeatureFlags)
(Maybe FeatureFlags)
-> CommandConnect -> Maybe FeatureFlags
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'featureFlags" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'featureFlags") CommandConnect
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: FeatureFlags
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 82)
((ByteString -> Builder)
-> (FeatureFlags -> ByteString) -> FeatureFlags -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
FeatureFlags -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
FeatureFlags
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandConnect CommandConnect FieldSet FieldSet
-> CommandConnect -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike FieldSet CommandConnect CommandConnect FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandConnect
_x)))))))))))
instance Control.DeepSeq.NFData CommandConnect where
rnf :: CommandConnect -> ()
rnf
= \ x__ :: CommandConnect
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> FieldSet
_CommandConnect'_unknownFields CommandConnect
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Text
_CommandConnect'clientVersion CommandConnect
x__)
(Maybe AuthMethod -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe AuthMethod
_CommandConnect'authMethod CommandConnect
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Text
_CommandConnect'authMethodName CommandConnect
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe ByteString
_CommandConnect'authData CommandConnect
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Int32
_CommandConnect'protocolVersion CommandConnect
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Text
_CommandConnect'proxyToBrokerUrl CommandConnect
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Text
_CommandConnect'originalPrincipal CommandConnect
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Text
_CommandConnect'originalAuthData CommandConnect
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe Text
_CommandConnect'originalAuthMethod CommandConnect
x__)
(Maybe FeatureFlags -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnect -> Maybe FeatureFlags
_CommandConnect'featureFlags CommandConnect
x__) ()))))))))))
data CommandConnected
= CommandConnected'_constructor {CommandConnected -> Text
_CommandConnected'serverVersion :: !Data.Text.Text,
CommandConnected -> Maybe Int32
_CommandConnected'protocolVersion :: !(Prelude.Maybe Data.Int.Int32),
CommandConnected -> Maybe Int32
_CommandConnected'maxMessageSize :: !(Prelude.Maybe Data.Int.Int32),
CommandConnected -> FieldSet
_CommandConnected'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandConnected -> CommandConnected -> Bool
(CommandConnected -> CommandConnected -> Bool)
-> (CommandConnected -> CommandConnected -> Bool)
-> Eq CommandConnected
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandConnected -> CommandConnected -> Bool
$c/= :: CommandConnected -> CommandConnected -> Bool
== :: CommandConnected -> CommandConnected -> Bool
$c== :: CommandConnected -> CommandConnected -> Bool
Prelude.Eq, Eq CommandConnected
Eq CommandConnected =>
(CommandConnected -> CommandConnected -> Ordering)
-> (CommandConnected -> CommandConnected -> Bool)
-> (CommandConnected -> CommandConnected -> Bool)
-> (CommandConnected -> CommandConnected -> Bool)
-> (CommandConnected -> CommandConnected -> Bool)
-> (CommandConnected -> CommandConnected -> CommandConnected)
-> (CommandConnected -> CommandConnected -> CommandConnected)
-> Ord CommandConnected
CommandConnected -> CommandConnected -> Bool
CommandConnected -> CommandConnected -> Ordering
CommandConnected -> CommandConnected -> CommandConnected
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandConnected -> CommandConnected -> CommandConnected
$cmin :: CommandConnected -> CommandConnected -> CommandConnected
max :: CommandConnected -> CommandConnected -> CommandConnected
$cmax :: CommandConnected -> CommandConnected -> CommandConnected
>= :: CommandConnected -> CommandConnected -> Bool
$c>= :: CommandConnected -> CommandConnected -> Bool
> :: CommandConnected -> CommandConnected -> Bool
$c> :: CommandConnected -> CommandConnected -> Bool
<= :: CommandConnected -> CommandConnected -> Bool
$c<= :: CommandConnected -> CommandConnected -> Bool
< :: CommandConnected -> CommandConnected -> Bool
$c< :: CommandConnected -> CommandConnected -> Bool
compare :: CommandConnected -> CommandConnected -> Ordering
$ccompare :: CommandConnected -> CommandConnected -> Ordering
$cp1Ord :: Eq CommandConnected
Prelude.Ord)
instance Prelude.Show CommandConnected where
showsPrec :: Int -> CommandConnected -> ShowS
showsPrec _ __x :: CommandConnected
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandConnected -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandConnected
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandConnected "serverVersion" Data.Text.Text where
fieldOf :: Proxy# "serverVersion"
-> (Text -> f Text) -> CommandConnected -> f CommandConnected
fieldOf _
= ((Text -> f Text) -> CommandConnected -> f CommandConnected)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandConnected
-> f CommandConnected
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnected -> Text)
-> (CommandConnected -> Text -> CommandConnected)
-> Lens CommandConnected CommandConnected Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> Text
_CommandConnected'serverVersion
(\ x__ :: CommandConnected
x__ y__ :: Text
y__ -> CommandConnected
x__ {_CommandConnected'serverVersion :: Text
_CommandConnected'serverVersion = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnected "protocolVersion" Data.Int.Int32 where
fieldOf :: Proxy# "protocolVersion"
-> (Int32 -> f Int32) -> CommandConnected -> f CommandConnected
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnected -> f CommandConnected)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandConnected
-> f CommandConnected
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnected -> Maybe Int32)
-> (CommandConnected -> Maybe Int32 -> CommandConnected)
-> Lens
CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> Maybe Int32
_CommandConnected'protocolVersion
(\ x__ :: CommandConnected
x__ y__ :: Maybe Int32
y__ -> CommandConnected
x__ {_CommandConnected'protocolVersion :: Maybe Int32
_CommandConnected'protocolVersion = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandConnected "maybe'protocolVersion" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'protocolVersion"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnected
-> f CommandConnected
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnected -> f CommandConnected)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnected
-> f CommandConnected
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnected -> Maybe Int32)
-> (CommandConnected -> Maybe Int32 -> CommandConnected)
-> Lens
CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> Maybe Int32
_CommandConnected'protocolVersion
(\ x__ :: CommandConnected
x__ y__ :: Maybe Int32
y__ -> CommandConnected
x__ {_CommandConnected'protocolVersion :: Maybe Int32
_CommandConnected'protocolVersion = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConnected "maxMessageSize" Data.Int.Int32 where
fieldOf :: Proxy# "maxMessageSize"
-> (Int32 -> f Int32) -> CommandConnected -> f CommandConnected
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnected -> f CommandConnected)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandConnected
-> f CommandConnected
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnected -> Maybe Int32)
-> (CommandConnected -> Maybe Int32 -> CommandConnected)
-> Lens
CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> Maybe Int32
_CommandConnected'maxMessageSize
(\ x__ :: CommandConnected
x__ y__ :: Maybe Int32
y__ -> CommandConnected
x__ {_CommandConnected'maxMessageSize :: Maybe Int32
_CommandConnected'maxMessageSize = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConnected "maybe'maxMessageSize" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'maxMessageSize"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnected
-> f CommandConnected
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandConnected -> f CommandConnected)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandConnected
-> f CommandConnected
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConnected -> Maybe Int32)
-> (CommandConnected -> Maybe Int32 -> CommandConnected)
-> Lens
CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> Maybe Int32
_CommandConnected'maxMessageSize
(\ x__ :: CommandConnected
x__ y__ :: Maybe Int32
y__ -> CommandConnected
x__ {_CommandConnected'maxMessageSize :: Maybe Int32
_CommandConnected'maxMessageSize = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandConnected where
messageName :: Proxy CommandConnected -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandConnected"
packedMessageDescriptor :: Proxy CommandConnected -> ByteString
packedMessageDescriptor _
= "\n\
\\DLECommandConnected\DC2%\n\
\\SOserver_version\CAN\SOH \STX(\tR\rserverVersion\DC2,\n\
\\DLEprotocol_version\CAN\STX \SOH(\ENQ:\SOH0R\SIprotocolVersion\DC2(\n\
\\DLEmax_message_size\CAN\ETX \SOH(\ENQR\SOmaxMessageSize"
packedFileDescriptor :: Proxy CommandConnected -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandConnected)
fieldsByTag
= let
serverVersion__field_descriptor :: FieldDescriptor CommandConnected
serverVersion__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConnected Text
-> FieldDescriptor CommandConnected
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"server_version"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandConnected CommandConnected Text Text
-> FieldAccessor CommandConnected Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"serverVersion")) ::
Data.ProtoLens.FieldDescriptor CommandConnected
protocolVersion__field_descriptor :: FieldDescriptor CommandConnected
protocolVersion__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandConnected Int32
-> FieldDescriptor CommandConnected
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"protocol_version"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandConnected Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion")) ::
Data.ProtoLens.FieldDescriptor CommandConnected
maxMessageSize__field_descriptor :: FieldDescriptor CommandConnected
maxMessageSize__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandConnected Int32
-> FieldDescriptor CommandConnected
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"max_message_size"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens CommandConnected CommandConnected (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandConnected Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'maxMessageSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'maxMessageSize")) ::
Data.ProtoLens.FieldDescriptor CommandConnected
in
[(Tag, FieldDescriptor CommandConnected)]
-> Map Tag (FieldDescriptor CommandConnected)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandConnected
serverVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandConnected
protocolVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandConnected
maxMessageSize__field_descriptor)]
unknownFields :: LensLike' f CommandConnected FieldSet
unknownFields
= (CommandConnected -> FieldSet)
-> (CommandConnected -> FieldSet -> CommandConnected)
-> Lens' CommandConnected FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConnected -> FieldSet
_CommandConnected'_unknownFields
(\ x__ :: CommandConnected
x__ y__ :: FieldSet
y__ -> CommandConnected
x__ {_CommandConnected'_unknownFields :: FieldSet
_CommandConnected'_unknownFields = FieldSet
y__})
defMessage :: CommandConnected
defMessage
= $WCommandConnected'_constructor :: Text -> Maybe Int32 -> Maybe Int32 -> FieldSet -> CommandConnected
CommandConnected'_constructor
{_CommandConnected'serverVersion :: Text
_CommandConnected'serverVersion = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandConnected'protocolVersion :: Maybe Int32
_CommandConnected'protocolVersion = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandConnected'maxMessageSize :: Maybe Int32
_CommandConnected'maxMessageSize = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandConnected'_unknownFields :: FieldSet
_CommandConnected'_unknownFields = []}
parseMessage :: Parser CommandConnected
parseMessage
= let
loop ::
CommandConnected
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandConnected
loop :: CommandConnected -> Bool -> Parser CommandConnected
loop x :: CommandConnected
x required'serverVersion :: Bool
required'serverVersion
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'serverVersion then
(:) "server_version"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandConnected -> Parser CommandConnected
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandConnected CommandConnected FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandConnected -> CommandConnected
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConnected CommandConnected FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandConnected
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"server_version"
CommandConnected -> Bool -> Parser CommandConnected
loop
(Setter CommandConnected CommandConnected Text Text
-> Text -> CommandConnected -> CommandConnected
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"serverVersion") Text
y CommandConnected
x)
Bool
Prelude.False
16
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"protocol_version"
CommandConnected -> Bool -> Parser CommandConnected
loop
(Setter CommandConnected CommandConnected Int32 Int32
-> Int32 -> CommandConnected -> CommandConnected
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"protocolVersion") Int32
y CommandConnected
x)
Bool
required'serverVersion
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"max_message_size"
CommandConnected -> Bool -> Parser CommandConnected
loop
(Setter CommandConnected CommandConnected Int32 Int32
-> Int32 -> CommandConnected -> CommandConnected
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "maxMessageSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maxMessageSize") Int32
y CommandConnected
x)
Bool
required'serverVersion
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandConnected -> Bool -> Parser CommandConnected
loop
(Setter CommandConnected CommandConnected FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandConnected -> CommandConnected
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConnected CommandConnected FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandConnected
x)
Bool
required'serverVersion
in
Parser CommandConnected -> String -> Parser CommandConnected
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandConnected -> Bool -> Parser CommandConnected
loop CommandConnected
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "CommandConnected"
buildMessage :: CommandConnected -> Builder
buildMessage
= \ _x :: CommandConnected
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandConnected CommandConnected Text Text
-> CommandConnected -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "serverVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"serverVersion") CommandConnected
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandConnected
CommandConnected
(Maybe Int32)
(Maybe Int32)
-> CommandConnected -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'protocolVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'protocolVersion") CommandConnected
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandConnected
CommandConnected
(Maybe Int32)
(Maybe Int32)
-> CommandConnected -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'maxMessageSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'maxMessageSize") CommandConnected
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandConnected CommandConnected FieldSet FieldSet
-> CommandConnected -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandConnected CommandConnected FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandConnected
_x))))
instance Control.DeepSeq.NFData CommandConnected where
rnf :: CommandConnected -> ()
rnf
= \ x__ :: CommandConnected
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnected -> FieldSet
_CommandConnected'_unknownFields CommandConnected
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnected -> Text
_CommandConnected'serverVersion CommandConnected
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnected -> Maybe Int32
_CommandConnected'protocolVersion CommandConnected
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConnected -> Maybe Int32
_CommandConnected'maxMessageSize CommandConnected
x__) ())))
data CommandConsumerStats
= CommandConsumerStats'_constructor {CommandConsumerStats -> Word64
_CommandConsumerStats'requestId :: !Data.Word.Word64,
CommandConsumerStats -> Word64
_CommandConsumerStats'consumerId :: !Data.Word.Word64,
CommandConsumerStats -> FieldSet
_CommandConsumerStats'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandConsumerStats -> CommandConsumerStats -> Bool
(CommandConsumerStats -> CommandConsumerStats -> Bool)
-> (CommandConsumerStats -> CommandConsumerStats -> Bool)
-> Eq CommandConsumerStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c/= :: CommandConsumerStats -> CommandConsumerStats -> Bool
== :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c== :: CommandConsumerStats -> CommandConsumerStats -> Bool
Prelude.Eq, Eq CommandConsumerStats
Eq CommandConsumerStats =>
(CommandConsumerStats -> CommandConsumerStats -> Ordering)
-> (CommandConsumerStats -> CommandConsumerStats -> Bool)
-> (CommandConsumerStats -> CommandConsumerStats -> Bool)
-> (CommandConsumerStats -> CommandConsumerStats -> Bool)
-> (CommandConsumerStats -> CommandConsumerStats -> Bool)
-> (CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats)
-> (CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats)
-> Ord CommandConsumerStats
CommandConsumerStats -> CommandConsumerStats -> Bool
CommandConsumerStats -> CommandConsumerStats -> Ordering
CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats
$cmin :: CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats
max :: CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats
$cmax :: CommandConsumerStats
-> CommandConsumerStats -> CommandConsumerStats
>= :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c>= :: CommandConsumerStats -> CommandConsumerStats -> Bool
> :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c> :: CommandConsumerStats -> CommandConsumerStats -> Bool
<= :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c<= :: CommandConsumerStats -> CommandConsumerStats -> Bool
< :: CommandConsumerStats -> CommandConsumerStats -> Bool
$c< :: CommandConsumerStats -> CommandConsumerStats -> Bool
compare :: CommandConsumerStats -> CommandConsumerStats -> Ordering
$ccompare :: CommandConsumerStats -> CommandConsumerStats -> Ordering
$cp1Ord :: Eq CommandConsumerStats
Prelude.Ord)
instance Prelude.Show CommandConsumerStats where
showsPrec :: Int -> CommandConsumerStats -> ShowS
showsPrec _ __x :: CommandConsumerStats
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandConsumerStats -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandConsumerStats
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandConsumerStats "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandConsumerStats
-> f CommandConsumerStats
fieldOf _
= ((Word64 -> f Word64)
-> CommandConsumerStats -> f CommandConsumerStats)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandConsumerStats
-> f CommandConsumerStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStats -> Word64)
-> (CommandConsumerStats -> Word64 -> CommandConsumerStats)
-> Lens CommandConsumerStats CommandConsumerStats Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStats -> Word64
_CommandConsumerStats'requestId
(\ x__ :: CommandConsumerStats
x__ y__ :: Word64
y__ -> CommandConsumerStats
x__ {_CommandConsumerStats'requestId :: Word64
_CommandConsumerStats'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStats "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandConsumerStats
-> f CommandConsumerStats
fieldOf _
= ((Word64 -> f Word64)
-> CommandConsumerStats -> f CommandConsumerStats)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandConsumerStats
-> f CommandConsumerStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStats -> Word64)
-> (CommandConsumerStats -> Word64 -> CommandConsumerStats)
-> Lens CommandConsumerStats CommandConsumerStats Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStats -> Word64
_CommandConsumerStats'consumerId
(\ x__ :: CommandConsumerStats
x__ y__ :: Word64
y__ -> CommandConsumerStats
x__ {_CommandConsumerStats'consumerId :: Word64
_CommandConsumerStats'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandConsumerStats where
messageName :: Proxy CommandConsumerStats -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandConsumerStats"
packedMessageDescriptor :: Proxy CommandConsumerStats -> ByteString
packedMessageDescriptor _
= "\n\
\\DC4CommandConsumerStats\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\US\n\
\\vconsumer_id\CAN\EOT \STX(\EOTR\n\
\consumerId"
packedFileDescriptor :: Proxy CommandConsumerStats -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandConsumerStats)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandConsumerStats
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStats Word64
-> FieldDescriptor CommandConsumerStats
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandConsumerStats CommandConsumerStats Word64 Word64
-> FieldAccessor CommandConsumerStats Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStats
consumerId__field_descriptor :: FieldDescriptor CommandConsumerStats
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStats Word64
-> FieldDescriptor CommandConsumerStats
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandConsumerStats CommandConsumerStats Word64 Word64
-> FieldAccessor CommandConsumerStats Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStats
in
[(Tag, FieldDescriptor CommandConsumerStats)]
-> Map Tag (FieldDescriptor CommandConsumerStats)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandConsumerStats
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandConsumerStats
consumerId__field_descriptor)]
unknownFields :: LensLike' f CommandConsumerStats FieldSet
unknownFields
= (CommandConsumerStats -> FieldSet)
-> (CommandConsumerStats -> FieldSet -> CommandConsumerStats)
-> Lens' CommandConsumerStats FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStats -> FieldSet
_CommandConsumerStats'_unknownFields
(\ x__ :: CommandConsumerStats
x__ y__ :: FieldSet
y__ -> CommandConsumerStats
x__ {_CommandConsumerStats'_unknownFields :: FieldSet
_CommandConsumerStats'_unknownFields = FieldSet
y__})
defMessage :: CommandConsumerStats
defMessage
= $WCommandConsumerStats'_constructor :: Word64 -> Word64 -> FieldSet -> CommandConsumerStats
CommandConsumerStats'_constructor
{_CommandConsumerStats'requestId :: Word64
_CommandConsumerStats'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandConsumerStats'consumerId :: Word64
_CommandConsumerStats'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandConsumerStats'_unknownFields :: FieldSet
_CommandConsumerStats'_unknownFields = []}
parseMessage :: Parser CommandConsumerStats
parseMessage
= let
loop ::
CommandConsumerStats
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandConsumerStats
loop :: CommandConsumerStats -> Bool -> Bool -> Parser CommandConsumerStats
loop x :: CommandConsumerStats
x required'consumerId :: Bool
required'consumerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandConsumerStats -> Parser CommandConsumerStats
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandConsumerStats CommandConsumerStats FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandConsumerStats
-> CommandConsumerStats
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConsumerStats CommandConsumerStats FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandConsumerStats
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandConsumerStats -> Bool -> Bool -> Parser CommandConsumerStats
loop
(Setter CommandConsumerStats CommandConsumerStats Word64 Word64
-> Word64 -> CommandConsumerStats -> CommandConsumerStats
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandConsumerStats
x)
Bool
required'consumerId
Bool
Prelude.False
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandConsumerStats -> Bool -> Bool -> Parser CommandConsumerStats
loop
(Setter CommandConsumerStats CommandConsumerStats Word64 Word64
-> Word64 -> CommandConsumerStats -> CommandConsumerStats
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandConsumerStats
x)
Bool
Prelude.False
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandConsumerStats -> Bool -> Bool -> Parser CommandConsumerStats
loop
(Setter CommandConsumerStats CommandConsumerStats FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandConsumerStats
-> CommandConsumerStats
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandConsumerStats CommandConsumerStats FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandConsumerStats
x)
Bool
required'consumerId
Bool
required'requestId
in
Parser CommandConsumerStats
-> String -> Parser CommandConsumerStats
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandConsumerStats -> Bool -> Bool -> Parser CommandConsumerStats
loop CommandConsumerStats
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandConsumerStats"
buildMessage :: CommandConsumerStats -> Builder
buildMessage
= \ _x :: CommandConsumerStats
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandConsumerStats CommandConsumerStats Word64 Word64
-> CommandConsumerStats -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandConsumerStats
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandConsumerStats CommandConsumerStats Word64 Word64
-> CommandConsumerStats -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandConsumerStats
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandConsumerStats
CommandConsumerStats
FieldSet
FieldSet
-> CommandConsumerStats -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandConsumerStats
CommandConsumerStats
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandConsumerStats
_x)))
instance Control.DeepSeq.NFData CommandConsumerStats where
rnf :: CommandConsumerStats -> ()
rnf
= \ x__ :: CommandConsumerStats
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStats -> FieldSet
_CommandConsumerStats'_unknownFields CommandConsumerStats
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStats -> Word64
_CommandConsumerStats'requestId CommandConsumerStats
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStats -> Word64
_CommandConsumerStats'consumerId CommandConsumerStats
x__) ()))
data CommandConsumerStatsResponse
= CommandConsumerStatsResponse'_constructor {CommandConsumerStatsResponse -> Word64
_CommandConsumerStatsResponse'requestId :: !Data.Word.Word64,
CommandConsumerStatsResponse -> Maybe ServerError
_CommandConsumerStatsResponse'errorCode :: !(Prelude.Maybe ServerError),
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'errorMessage :: !(Prelude.Maybe Data.Text.Text),
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateOut :: !(Prelude.Maybe Prelude.Double),
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut :: !(Prelude.Maybe Prelude.Double),
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver :: !(Prelude.Maybe Prelude.Double),
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'consumerName :: !(Prelude.Maybe Data.Text.Text),
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'availablePermits :: !(Prelude.Maybe Data.Word.Word64),
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'unackedMessages :: !(Prelude.Maybe Data.Word.Word64),
CommandConsumerStatsResponse -> Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs :: !(Prelude.Maybe Prelude.Bool),
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'address :: !(Prelude.Maybe Data.Text.Text),
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'connectedSince :: !(Prelude.Maybe Data.Text.Text),
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'type' :: !(Prelude.Maybe Data.Text.Text),
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateExpired :: !(Prelude.Maybe Prelude.Double),
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'msgBacklog :: !(Prelude.Maybe Data.Word.Word64),
CommandConsumerStatsResponse -> FieldSet
_CommandConsumerStatsResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
(CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> Eq CommandConsumerStatsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c/= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
== :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c== :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
Prelude.Eq, Eq CommandConsumerStatsResponse
Eq CommandConsumerStatsResponse =>
(CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Ordering)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse)
-> (CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse)
-> Ord CommandConsumerStatsResponse
CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Ordering
CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse
$cmin :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse
max :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse
$cmax :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> CommandConsumerStatsResponse
>= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c>= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
> :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c> :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
<= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c<= :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
< :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
$c< :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Bool
compare :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Ordering
$ccompare :: CommandConsumerStatsResponse
-> CommandConsumerStatsResponse -> Ordering
$cp1Ord :: Eq CommandConsumerStatsResponse
Prelude.Ord)
instance Prelude.Show CommandConsumerStatsResponse where
showsPrec :: Int -> CommandConsumerStatsResponse -> ShowS
showsPrec _ __x :: CommandConsumerStatsResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandConsumerStatsResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandConsumerStatsResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Word64)
-> (CommandConsumerStatsResponse
-> Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Word64
_CommandConsumerStatsResponse'requestId
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Word64
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'requestId :: Word64
_CommandConsumerStatsResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "errorCode" ServerError where
fieldOf :: Proxy# "errorCode"
-> (ServerError -> f ServerError)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe ServerError)
-> (CommandConsumerStatsResponse
-> Maybe ServerError -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe ServerError
_CommandConsumerStatsResponse'errorCode
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe ServerError
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'errorCode :: Maybe ServerError
_CommandConsumerStatsResponse'errorCode = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'errorCode" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'errorCode"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe ServerError)
-> (CommandConsumerStatsResponse
-> Maybe ServerError -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe ServerError
_CommandConsumerStatsResponse'errorCode
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe ServerError
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'errorCode :: Maybe ServerError
_CommandConsumerStatsResponse'errorCode = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "errorMessage" Data.Text.Text where
fieldOf :: Proxy# "errorMessage"
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'errorMessage
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'errorMessage :: Maybe Text
_CommandConsumerStatsResponse'errorMessage = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'errorMessage" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'errorMessage"
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'errorMessage
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'errorMessage :: Maybe Text
_CommandConsumerStatsResponse'errorMessage = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "msgRateOut" Prelude.Double where
fieldOf :: Proxy# "msgRateOut"
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Double -> f Double) -> Maybe Double -> f (Maybe Double))
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateOut
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateOut :: Maybe Double
_CommandConsumerStatsResponse'msgRateOut = Maybe Double
y__}))
(Double -> Lens' (Maybe Double) Double
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Double
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'msgRateOut" (Prelude.Maybe Prelude.Double) where
fieldOf :: Proxy# "maybe'msgRateOut"
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double))
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateOut
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateOut :: Maybe Double
_CommandConsumerStatsResponse'msgRateOut = Maybe Double
y__}))
(Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "msgThroughputOut" Prelude.Double where
fieldOf :: Proxy# "msgThroughputOut"
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Double -> f Double) -> Maybe Double -> f (Maybe Double))
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgThroughputOut :: Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut = Maybe Double
y__}))
(Double -> Lens' (Maybe Double) Double
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Double
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'msgThroughputOut" (Prelude.Maybe Prelude.Double) where
fieldOf :: Proxy# "maybe'msgThroughputOut"
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double))
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgThroughputOut :: Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut = Maybe Double
y__}))
(Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "msgRateRedeliver" Prelude.Double where
fieldOf :: Proxy# "msgRateRedeliver"
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Double -> f Double) -> Maybe Double -> f (Maybe Double))
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateRedeliver :: Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver = Maybe Double
y__}))
(Double -> Lens' (Maybe Double) Double
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Double
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'msgRateRedeliver" (Prelude.Maybe Prelude.Double) where
fieldOf :: Proxy# "maybe'msgRateRedeliver"
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double))
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateRedeliver :: Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver = Maybe Double
y__}))
(Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "consumerName" Data.Text.Text where
fieldOf :: Proxy# "consumerName"
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'consumerName
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'consumerName :: Maybe Text
_CommandConsumerStatsResponse'consumerName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'consumerName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'consumerName"
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'consumerName
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'consumerName :: Maybe Text
_CommandConsumerStatsResponse'consumerName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "availablePermits" Data.Word.Word64 where
fieldOf :: Proxy# "availablePermits"
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'availablePermits
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'availablePermits :: Maybe Word64
_CommandConsumerStatsResponse'availablePermits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'availablePermits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'availablePermits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'availablePermits
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'availablePermits :: Maybe Word64
_CommandConsumerStatsResponse'availablePermits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "unackedMessages" Data.Word.Word64 where
fieldOf :: Proxy# "unackedMessages"
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'unackedMessages
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'unackedMessages :: Maybe Word64
_CommandConsumerStatsResponse'unackedMessages = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'unackedMessages" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'unackedMessages"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'unackedMessages
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'unackedMessages :: Maybe Word64
_CommandConsumerStatsResponse'unackedMessages = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "blockedConsumerOnUnackedMsgs" Prelude.Bool where
fieldOf :: Proxy# "blockedConsumerOnUnackedMsgs"
-> (Bool -> f Bool)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Bool)
-> (CommandConsumerStatsResponse
-> Maybe Bool -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Bool
y__
-> CommandConsumerStatsResponse
x__
{_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs :: Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'blockedConsumerOnUnackedMsgs" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'blockedConsumerOnUnackedMsgs"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Bool)
-> (CommandConsumerStatsResponse
-> Maybe Bool -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Bool
y__
-> CommandConsumerStatsResponse
x__
{_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs :: Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "address" Data.Text.Text where
fieldOf :: Proxy# "address"
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'address
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'address :: Maybe Text
_CommandConsumerStatsResponse'address = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'address" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'address"
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'address
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'address :: Maybe Text
_CommandConsumerStatsResponse'address = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "connectedSince" Data.Text.Text where
fieldOf :: Proxy# "connectedSince"
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'connectedSince
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'connectedSince :: Maybe Text
_CommandConsumerStatsResponse'connectedSince = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'connectedSince" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'connectedSince"
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'connectedSince
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'connectedSince :: Maybe Text
_CommandConsumerStatsResponse'connectedSince = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "type'" Data.Text.Text where
fieldOf :: Proxy# "type'"
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'type'
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'type' :: Maybe Text
_CommandConsumerStatsResponse'type' = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'type'" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'type'"
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Text)
-> (CommandConsumerStatsResponse
-> Maybe Text -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'type'
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Text
y__ -> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'type' :: Maybe Text
_CommandConsumerStatsResponse'type' = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "msgRateExpired" Prelude.Double where
fieldOf :: Proxy# "msgRateExpired"
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Double -> f Double) -> Maybe Double -> f (Maybe Double))
-> (Double -> f Double)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateExpired
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateExpired :: Maybe Double
_CommandConsumerStatsResponse'msgRateExpired = Maybe Double
y__}))
(Double -> Lens' (Maybe Double) Double
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Double
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'msgRateExpired" (Prelude.Maybe Prelude.Double) where
fieldOf :: Proxy# "maybe'msgRateExpired"
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double))
-> (Maybe Double -> f (Maybe Double))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Double)
-> (CommandConsumerStatsResponse
-> Maybe Double -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateExpired
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Double
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgRateExpired :: Maybe Double
_CommandConsumerStatsResponse'msgRateExpired = Maybe Double
y__}))
(Maybe Double -> f (Maybe Double))
-> Maybe Double -> f (Maybe Double)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "msgBacklog" Data.Word.Word64 where
fieldOf :: Proxy# "msgBacklog"
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'msgBacklog
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgBacklog :: Maybe Word64
_CommandConsumerStatsResponse'msgBacklog = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandConsumerStatsResponse "maybe'msgBacklog" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'msgBacklog"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse -> f CommandConsumerStatsResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandConsumerStatsResponse
-> f CommandConsumerStatsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandConsumerStatsResponse -> Maybe Word64)
-> (CommandConsumerStatsResponse
-> Maybe Word64 -> CommandConsumerStatsResponse)
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'msgBacklog
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: Maybe Word64
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'msgBacklog :: Maybe Word64
_CommandConsumerStatsResponse'msgBacklog = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandConsumerStatsResponse where
messageName :: Proxy CommandConsumerStatsResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandConsumerStatsResponse"
packedMessageDescriptor :: Proxy CommandConsumerStatsResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\FSCommandConsumerStatsResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2\RS\n\
\\n\
\msgRateOut\CAN\EOT \SOH(\SOHR\n\
\msgRateOut\DC2*\n\
\\DLEmsgThroughputOut\CAN\ENQ \SOH(\SOHR\DLEmsgThroughputOut\DC2*\n\
\\DLEmsgRateRedeliver\CAN\ACK \SOH(\SOHR\DLEmsgRateRedeliver\DC2\"\n\
\\fconsumerName\CAN\a \SOH(\tR\fconsumerName\DC2*\n\
\\DLEavailablePermits\CAN\b \SOH(\EOTR\DLEavailablePermits\DC2(\n\
\\SIunackedMessages\CAN\t \SOH(\EOTR\SIunackedMessages\DC2B\n\
\\FSblockedConsumerOnUnackedMsgs\CAN\n\
\ \SOH(\bR\FSblockedConsumerOnUnackedMsgs\DC2\CAN\n\
\\aaddress\CAN\v \SOH(\tR\aaddress\DC2&\n\
\\SOconnectedSince\CAN\f \SOH(\tR\SOconnectedSince\DC2\DC2\n\
\\EOTtype\CAN\r \SOH(\tR\EOTtype\DC2&\n\
\\SOmsgRateExpired\CAN\SO \SOH(\SOHR\SOmsgRateExpired\DC2\RS\n\
\\n\
\msgBacklog\CAN\SI \SOH(\EOTR\n\
\msgBacklog"
packedFileDescriptor :: Proxy CommandConsumerStatsResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandConsumerStatsResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStatsResponse Word64
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> FieldAccessor CommandConsumerStatsResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
errorCode__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
errorCode__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandConsumerStatsResponse ServerError
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_code"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandConsumerStatsResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
errorMessage__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
errorMessage__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConsumerStatsResponse Text
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandConsumerStatsResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
msgRateOut__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
msgRateOut__field_descriptor
= String
-> FieldTypeDescriptor Double
-> FieldAccessor CommandConsumerStatsResponse Double
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"msgRateOut"
(ScalarField Double -> FieldTypeDescriptor Double
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Double
Data.ProtoLens.DoubleField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Double)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> FieldAccessor CommandConsumerStatsResponse Double
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgRateOut")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
msgThroughputOut__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
msgThroughputOut__field_descriptor
= String
-> FieldTypeDescriptor Double
-> FieldAccessor CommandConsumerStatsResponse Double
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"msgThroughputOut"
(ScalarField Double -> FieldTypeDescriptor Double
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Double
Data.ProtoLens.DoubleField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Double)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> FieldAccessor CommandConsumerStatsResponse Double
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'msgThroughputOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgThroughputOut")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
msgRateRedeliver__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
msgRateRedeliver__field_descriptor
= String
-> FieldTypeDescriptor Double
-> FieldAccessor CommandConsumerStatsResponse Double
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"msgRateRedeliver"
(ScalarField Double -> FieldTypeDescriptor Double
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Double
Data.ProtoLens.DoubleField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Double)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> FieldAccessor CommandConsumerStatsResponse Double
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateRedeliver" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgRateRedeliver")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
consumerName__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
consumerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConsumerStatsResponse Text
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumerName"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandConsumerStatsResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerName")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
availablePermits__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
availablePermits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStatsResponse Word64
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"availablePermits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandConsumerStatsResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'availablePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'availablePermits")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
unackedMessages__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
unackedMessages__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStatsResponse Word64
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"unackedMessages"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandConsumerStatsResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'unackedMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'unackedMessages")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
blockedConsumerOnUnackedMsgs__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
blockedConsumerOnUnackedMsgs__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandConsumerStatsResponse Bool
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"blockedConsumerOnUnackedMsgs"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor CommandConsumerStatsResponse Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'blockedConsumerOnUnackedMsgs" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'blockedConsumerOnUnackedMsgs")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
address__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
address__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConsumerStatsResponse Text
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"address"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandConsumerStatsResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'address" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'address")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
connectedSince__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
connectedSince__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConsumerStatsResponse Text
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"connectedSince"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandConsumerStatsResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'connectedSince" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'connectedSince")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
type'__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
type'__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandConsumerStatsResponse Text
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"type"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandConsumerStatsResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'type'")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
msgRateExpired__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
msgRateExpired__field_descriptor
= String
-> FieldTypeDescriptor Double
-> FieldAccessor CommandConsumerStatsResponse Double
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"msgRateExpired"
(ScalarField Double -> FieldTypeDescriptor Double
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Double
Data.ProtoLens.DoubleField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Double)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> FieldAccessor CommandConsumerStatsResponse Double
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateExpired" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgRateExpired")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
msgBacklog__field_descriptor :: FieldDescriptor CommandConsumerStatsResponse
msgBacklog__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandConsumerStatsResponse Word64
-> FieldDescriptor CommandConsumerStatsResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"msgBacklog"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandConsumerStatsResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'msgBacklog" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgBacklog")) ::
Data.ProtoLens.FieldDescriptor CommandConsumerStatsResponse
in
[(Tag, FieldDescriptor CommandConsumerStatsResponse)]
-> Map Tag (FieldDescriptor CommandConsumerStatsResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandConsumerStatsResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandConsumerStatsResponse
errorCode__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandConsumerStatsResponse
errorMessage__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandConsumerStatsResponse
msgRateOut__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandConsumerStatsResponse
msgThroughputOut__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandConsumerStatsResponse
msgRateRedeliver__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandConsumerStatsResponse
consumerName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor CommandConsumerStatsResponse
availablePermits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor CommandConsumerStatsResponse
unackedMessages__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 10,
FieldDescriptor CommandConsumerStatsResponse
blockedConsumerOnUnackedMsgs__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 11, FieldDescriptor CommandConsumerStatsResponse
address__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 12, FieldDescriptor CommandConsumerStatsResponse
connectedSince__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 13, FieldDescriptor CommandConsumerStatsResponse
type'__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 14, FieldDescriptor CommandConsumerStatsResponse
msgRateExpired__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 15, FieldDescriptor CommandConsumerStatsResponse
msgBacklog__field_descriptor)]
unknownFields :: LensLike' f CommandConsumerStatsResponse FieldSet
unknownFields
= (CommandConsumerStatsResponse -> FieldSet)
-> (CommandConsumerStatsResponse
-> FieldSet -> CommandConsumerStatsResponse)
-> Lens' CommandConsumerStatsResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandConsumerStatsResponse -> FieldSet
_CommandConsumerStatsResponse'_unknownFields
(\ x__ :: CommandConsumerStatsResponse
x__ y__ :: FieldSet
y__
-> CommandConsumerStatsResponse
x__ {_CommandConsumerStatsResponse'_unknownFields :: FieldSet
_CommandConsumerStatsResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandConsumerStatsResponse
defMessage
= $WCommandConsumerStatsResponse'_constructor :: Word64
-> Maybe ServerError
-> Maybe Text
-> Maybe Double
-> Maybe Double
-> Maybe Double
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Double
-> Maybe Word64
-> FieldSet
-> CommandConsumerStatsResponse
CommandConsumerStatsResponse'_constructor
{_CommandConsumerStatsResponse'requestId :: Word64
_CommandConsumerStatsResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandConsumerStatsResponse'errorCode :: Maybe ServerError
_CommandConsumerStatsResponse'errorCode = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'errorMessage :: Maybe Text
_CommandConsumerStatsResponse'errorMessage = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'msgRateOut :: Maybe Double
_CommandConsumerStatsResponse'msgRateOut = Maybe Double
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'msgThroughputOut :: Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut = Maybe Double
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'msgRateRedeliver :: Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver = Maybe Double
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'consumerName :: Maybe Text
_CommandConsumerStatsResponse'consumerName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'availablePermits :: Maybe Word64
_CommandConsumerStatsResponse'availablePermits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'unackedMessages :: Maybe Word64
_CommandConsumerStatsResponse'unackedMessages = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs :: Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'address :: Maybe Text
_CommandConsumerStatsResponse'address = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'connectedSince :: Maybe Text
_CommandConsumerStatsResponse'connectedSince = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'type' :: Maybe Text
_CommandConsumerStatsResponse'type' = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'msgRateExpired :: Maybe Double
_CommandConsumerStatsResponse'msgRateExpired = Maybe Double
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'msgBacklog :: Maybe Word64
_CommandConsumerStatsResponse'msgBacklog = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandConsumerStatsResponse'_unknownFields :: FieldSet
_CommandConsumerStatsResponse'_unknownFields = []}
parseMessage :: Parser CommandConsumerStatsResponse
parseMessage
= let
loop ::
CommandConsumerStatsResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandConsumerStatsResponse
loop :: CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop x :: CommandConsumerStatsResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandConsumerStatsResponse -> Parser CommandConsumerStatsResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandConsumerStatsResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> Word64
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandConsumerStatsResponse
x)
Bool
Prelude.False
16
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error_code"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
ServerError
ServerError
-> ServerError
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorCode") ServerError
y CommandConsumerStatsResponse
x)
Bool
required'requestId
26
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"error_message"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Text Text
-> Text
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorMessage") Text
y CommandConsumerStatsResponse
x)
Bool
required'requestId
33
-> do Double
y <- Parser Double -> String -> Parser Double
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Double) -> Parser Word64 -> Parser Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Double
Data.ProtoLens.Encoding.Bytes.wordToDouble
Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64)
"msgRateOut"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Double
Double
-> Double
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "msgRateOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"msgRateOut") Double
y CommandConsumerStatsResponse
x)
Bool
required'requestId
41
-> do Double
y <- Parser Double -> String -> Parser Double
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Double) -> Parser Word64 -> Parser Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Double
Data.ProtoLens.Encoding.Bytes.wordToDouble
Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64)
"msgThroughputOut"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Double
Double
-> Double
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "msgThroughputOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"msgThroughputOut") Double
y CommandConsumerStatsResponse
x)
Bool
required'requestId
49
-> do Double
y <- Parser Double -> String -> Parser Double
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Double) -> Parser Word64 -> Parser Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Double
Data.ProtoLens.Encoding.Bytes.wordToDouble
Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64)
"msgRateRedeliver"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Double
Double
-> Double
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "msgRateRedeliver" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"msgRateRedeliver") Double
y CommandConsumerStatsResponse
x)
Bool
required'requestId
58
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"consumerName"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Text Text
-> Text
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerName") Text
y CommandConsumerStatsResponse
x)
Bool
required'requestId
64
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "availablePermits"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> Word64
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "availablePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"availablePermits") Word64
y CommandConsumerStatsResponse
x)
Bool
required'requestId
72
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "unackedMessages"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> Word64
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "unackedMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"unackedMessages") Word64
y CommandConsumerStatsResponse
x)
Bool
required'requestId
80
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"blockedConsumerOnUnackedMsgs"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Bool Bool
-> Bool
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "blockedConsumerOnUnackedMsgs" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"blockedConsumerOnUnackedMsgs")
Bool
y
CommandConsumerStatsResponse
x)
Bool
required'requestId
90
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"address"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Text Text
-> Text
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "address" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"address") Text
y CommandConsumerStatsResponse
x)
Bool
required'requestId
98
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"connectedSince"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Text Text
-> Text
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "connectedSince" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"connectedSince") Text
y CommandConsumerStatsResponse
x)
Bool
required'requestId
106
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"type"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse CommandConsumerStatsResponse Text Text
-> Text
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'") Text
y CommandConsumerStatsResponse
x)
Bool
required'requestId
113
-> do Double
y <- Parser Double -> String -> Parser Double
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Double) -> Parser Word64 -> Parser Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Double
Data.ProtoLens.Encoding.Bytes.wordToDouble
Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64)
"msgRateExpired"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Double
Double
-> Double
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "msgRateExpired" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"msgRateExpired") Double
y CommandConsumerStatsResponse
x)
Bool
required'requestId
120
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "msgBacklog"
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> Word64
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "msgBacklog" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"msgBacklog") Word64
y CommandConsumerStatsResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop
(Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandConsumerStatsResponse
-> CommandConsumerStatsResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandConsumerStatsResponse
x)
Bool
required'requestId
in
Parser CommandConsumerStatsResponse
-> String -> Parser CommandConsumerStatsResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandConsumerStatsResponse
-> Bool -> Parser CommandConsumerStatsResponse
loop CommandConsumerStatsResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandConsumerStatsResponse"
buildMessage :: CommandConsumerStatsResponse -> Builder
buildMessage
= \ _x :: CommandConsumerStatsResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandConsumerStatsResponse
CommandConsumerStatsResponse
Word64
Word64
-> CommandConsumerStatsResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandConsumerStatsResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandConsumerStatsResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> CommandConsumerStatsResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Double)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> CommandConsumerStatsResponse -> Maybe Double
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgRateOut") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Double
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 33)
((Word64 -> Builder) -> (Double -> Word64) -> Double -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64
Double -> Word64
Data.ProtoLens.Encoding.Bytes.doubleToWord
Double
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Double)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> CommandConsumerStatsResponse -> Maybe Double
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'msgThroughputOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgThroughputOut") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Double
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 41)
((Word64 -> Builder) -> (Double -> Word64) -> Double -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64
Double -> Word64
Data.ProtoLens.Encoding.Bytes.doubleToWord
Double
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Double)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> CommandConsumerStatsResponse -> Maybe Double
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateRedeliver" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'msgRateRedeliver") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Double
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 49)
((Word64 -> Builder) -> (Double -> Word64) -> Double -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64
Double -> Word64
Data.ProtoLens.Encoding.Bytes.doubleToWord
Double
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> CommandConsumerStatsResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerName") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> CommandConsumerStatsResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'availablePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'availablePermits") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> CommandConsumerStatsResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'unackedMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'unackedMessages") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 72)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Bool)
(Maybe Bool)
-> CommandConsumerStatsResponse -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'blockedConsumerOnUnackedMsgs" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'blockedConsumerOnUnackedMsgs")
CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 80)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> CommandConsumerStatsResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'address" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'address") CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 90)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> CommandConsumerStatsResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'connectedSince" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'connectedSince")
CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 98)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Text)
(Maybe Text)
-> CommandConsumerStatsResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'type'")
CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
106)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Double)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Double)
(Maybe Double)
-> CommandConsumerStatsResponse -> Maybe Double
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'msgRateExpired" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'msgRateExpired")
CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Double
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
113)
((Word64 -> Builder) -> (Double -> Word64) -> Double -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64
Double -> Word64
Data.ProtoLens.Encoding.Bytes.doubleToWord
Double
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandConsumerStatsResponse
CommandConsumerStatsResponse
(Maybe Word64)
(Maybe Word64)
-> CommandConsumerStatsResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'msgBacklog" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'msgBacklog")
CommandConsumerStatsResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
120)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word64
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
-> CommandConsumerStatsResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike
FieldSet
CommandConsumerStatsResponse
CommandConsumerStatsResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields
CommandConsumerStatsResponse
_x))))))))))))))))
instance Control.DeepSeq.NFData CommandConsumerStatsResponse where
rnf :: CommandConsumerStatsResponse -> ()
rnf
= \ x__ :: CommandConsumerStatsResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> FieldSet
_CommandConsumerStatsResponse'_unknownFields CommandConsumerStatsResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Word64
_CommandConsumerStatsResponse'requestId CommandConsumerStatsResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe ServerError
_CommandConsumerStatsResponse'errorCode CommandConsumerStatsResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'errorMessage CommandConsumerStatsResponse
x__)
(Maybe Double -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateOut CommandConsumerStatsResponse
x__)
(Maybe Double -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgThroughputOut CommandConsumerStatsResponse
x__)
(Maybe Double -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateRedeliver CommandConsumerStatsResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'consumerName CommandConsumerStatsResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'availablePermits CommandConsumerStatsResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'unackedMessages CommandConsumerStatsResponse
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Bool
_CommandConsumerStatsResponse'blockedConsumerOnUnackedMsgs
CommandConsumerStatsResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'address CommandConsumerStatsResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'connectedSince CommandConsumerStatsResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Text
_CommandConsumerStatsResponse'type' CommandConsumerStatsResponse
x__)
(Maybe Double -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Double
_CommandConsumerStatsResponse'msgRateExpired
CommandConsumerStatsResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandConsumerStatsResponse -> Maybe Word64
_CommandConsumerStatsResponse'msgBacklog
CommandConsumerStatsResponse
x__)
())))))))))))))))
data CommandEndTxn
= CommandEndTxn'_constructor {CommandEndTxn -> Word64
_CommandEndTxn'requestId :: !Data.Word.Word64,
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxn -> Maybe TxnAction
_CommandEndTxn'txnAction :: !(Prelude.Maybe TxnAction),
CommandEndTxn -> FieldSet
_CommandEndTxn'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxn -> CommandEndTxn -> Bool
(CommandEndTxn -> CommandEndTxn -> Bool)
-> (CommandEndTxn -> CommandEndTxn -> Bool) -> Eq CommandEndTxn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxn -> CommandEndTxn -> Bool
$c/= :: CommandEndTxn -> CommandEndTxn -> Bool
== :: CommandEndTxn -> CommandEndTxn -> Bool
$c== :: CommandEndTxn -> CommandEndTxn -> Bool
Prelude.Eq, Eq CommandEndTxn
Eq CommandEndTxn =>
(CommandEndTxn -> CommandEndTxn -> Ordering)
-> (CommandEndTxn -> CommandEndTxn -> Bool)
-> (CommandEndTxn -> CommandEndTxn -> Bool)
-> (CommandEndTxn -> CommandEndTxn -> Bool)
-> (CommandEndTxn -> CommandEndTxn -> Bool)
-> (CommandEndTxn -> CommandEndTxn -> CommandEndTxn)
-> (CommandEndTxn -> CommandEndTxn -> CommandEndTxn)
-> Ord CommandEndTxn
CommandEndTxn -> CommandEndTxn -> Bool
CommandEndTxn -> CommandEndTxn -> Ordering
CommandEndTxn -> CommandEndTxn -> CommandEndTxn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxn -> CommandEndTxn -> CommandEndTxn
$cmin :: CommandEndTxn -> CommandEndTxn -> CommandEndTxn
max :: CommandEndTxn -> CommandEndTxn -> CommandEndTxn
$cmax :: CommandEndTxn -> CommandEndTxn -> CommandEndTxn
>= :: CommandEndTxn -> CommandEndTxn -> Bool
$c>= :: CommandEndTxn -> CommandEndTxn -> Bool
> :: CommandEndTxn -> CommandEndTxn -> Bool
$c> :: CommandEndTxn -> CommandEndTxn -> Bool
<= :: CommandEndTxn -> CommandEndTxn -> Bool
$c<= :: CommandEndTxn -> CommandEndTxn -> Bool
< :: CommandEndTxn -> CommandEndTxn -> Bool
$c< :: CommandEndTxn -> CommandEndTxn -> Bool
compare :: CommandEndTxn -> CommandEndTxn -> Ordering
$ccompare :: CommandEndTxn -> CommandEndTxn -> Ordering
$cp1Ord :: Eq CommandEndTxn
Prelude.Ord)
instance Prelude.Show CommandEndTxn where
showsPrec :: Int -> CommandEndTxn -> ShowS
showsPrec _ __x :: CommandEndTxn
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxn -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxn
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxn "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandEndTxn -> f CommandEndTxn
fieldOf _
= ((Word64 -> f Word64) -> CommandEndTxn -> f CommandEndTxn)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Word64)
-> (CommandEndTxn -> Word64 -> CommandEndTxn)
-> Lens CommandEndTxn CommandEndTxn Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Word64
_CommandEndTxn'requestId
(\ x__ :: CommandEndTxn
x__ y__ :: Word64
y__ -> CommandEndTxn
x__ {_CommandEndTxn'requestId :: Word64
_CommandEndTxn'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxn "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64) -> CommandEndTxn -> f CommandEndTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn -> f CommandEndTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe Word64)
-> (CommandEndTxn -> Maybe Word64 -> CommandEndTxn)
-> Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidLeastBits
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe Word64
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnidLeastBits :: Maybe Word64
_CommandEndTxn'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxn "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn
-> f CommandEndTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn -> f CommandEndTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe Word64)
-> (CommandEndTxn -> Maybe Word64 -> CommandEndTxn)
-> Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidLeastBits
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe Word64
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnidLeastBits :: Maybe Word64
_CommandEndTxn'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxn "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64) -> CommandEndTxn -> f CommandEndTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn -> f CommandEndTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe Word64)
-> (CommandEndTxn -> Maybe Word64 -> CommandEndTxn)
-> Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidMostBits
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe Word64
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnidMostBits :: Maybe Word64
_CommandEndTxn'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxn "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn
-> f CommandEndTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn -> f CommandEndTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe Word64)
-> (CommandEndTxn -> Maybe Word64 -> CommandEndTxn)
-> Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidMostBits
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe Word64
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnidMostBits :: Maybe Word64
_CommandEndTxn'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxn "txnAction" TxnAction where
fieldOf :: Proxy# "txnAction"
-> (TxnAction -> f TxnAction) -> CommandEndTxn -> f CommandEndTxn
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxn -> f CommandEndTxn)
-> ((TxnAction -> f TxnAction)
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (TxnAction -> f TxnAction)
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe TxnAction)
-> (CommandEndTxn -> Maybe TxnAction -> CommandEndTxn)
-> Lens
CommandEndTxn CommandEndTxn (Maybe TxnAction) (Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe TxnAction
_CommandEndTxn'txnAction
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnAction :: Maybe TxnAction
_CommandEndTxn'txnAction = Maybe TxnAction
y__}))
(TxnAction -> Lens' (Maybe TxnAction) TxnAction
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens TxnAction
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxn "maybe'txnAction" (Prelude.Maybe TxnAction) where
fieldOf :: Proxy# "maybe'txnAction"
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxn
-> f CommandEndTxn
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxn -> f CommandEndTxn)
-> ((Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxn
-> f CommandEndTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxn -> Maybe TxnAction)
-> (CommandEndTxn -> Maybe TxnAction -> CommandEndTxn)
-> Lens
CommandEndTxn CommandEndTxn (Maybe TxnAction) (Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> Maybe TxnAction
_CommandEndTxn'txnAction
(\ x__ :: CommandEndTxn
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxn
x__ {_CommandEndTxn'txnAction :: Maybe TxnAction
_CommandEndTxn'txnAction = Maybe TxnAction
y__}))
(Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxn where
messageName :: Proxy CommandEndTxn -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxn"
packedMessageDescriptor :: Proxy CommandEndTxn -> ByteString
packedMessageDescriptor _
= "\n\
\\rCommandEndTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC26\n\
\\n\
\txn_action\CAN\EOT \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction"
packedFileDescriptor :: Proxy CommandEndTxn -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxn)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxn
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxn Word64
-> FieldDescriptor CommandEndTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandEndTxn CommandEndTxn Word64 Word64
-> FieldAccessor CommandEndTxn Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxn
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxn
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxn Word64
-> FieldDescriptor CommandEndTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandEndTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxn
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxn
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxn Word64
-> FieldDescriptor CommandEndTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandEndTxn CommandEndTxn (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandEndTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxn
txnAction__field_descriptor :: FieldDescriptor CommandEndTxn
txnAction__field_descriptor
= String
-> FieldTypeDescriptor TxnAction
-> FieldAccessor CommandEndTxn TxnAction
-> FieldDescriptor CommandEndTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txn_action"
(ScalarField TxnAction -> FieldTypeDescriptor TxnAction
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField TxnAction
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor TxnAction)
(Lens
CommandEndTxn CommandEndTxn (Maybe TxnAction) (Maybe TxnAction)
-> FieldAccessor CommandEndTxn TxnAction
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxn
in
[(Tag, FieldDescriptor CommandEndTxn)]
-> Map Tag (FieldDescriptor CommandEndTxn)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxn
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxn
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxn
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxn
txnAction__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxn FieldSet
unknownFields
= (CommandEndTxn -> FieldSet)
-> (CommandEndTxn -> FieldSet -> CommandEndTxn)
-> Lens' CommandEndTxn FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxn -> FieldSet
_CommandEndTxn'_unknownFields
(\ x__ :: CommandEndTxn
x__ y__ :: FieldSet
y__ -> CommandEndTxn
x__ {_CommandEndTxn'_unknownFields :: FieldSet
_CommandEndTxn'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxn
defMessage
= $WCommandEndTxn'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe TxnAction
-> FieldSet
-> CommandEndTxn
CommandEndTxn'_constructor
{_CommandEndTxn'requestId :: Word64
_CommandEndTxn'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxn'txnidLeastBits :: Maybe Word64
_CommandEndTxn'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxn'txnidMostBits :: Maybe Word64
_CommandEndTxn'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxn'txnAction :: Maybe TxnAction
_CommandEndTxn'txnAction = Maybe TxnAction
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxn'_unknownFields :: FieldSet
_CommandEndTxn'_unknownFields = []}
parseMessage :: Parser CommandEndTxn
parseMessage
= let
loop ::
CommandEndTxn
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxn
loop :: CommandEndTxn -> Bool -> Parser CommandEndTxn
loop x :: CommandEndTxn
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxn -> Parser CommandEndTxn
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandEndTxn CommandEndTxn FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandEndTxn CommandEndTxn FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxn
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxn -> Bool -> Parser CommandEndTxn
loop
(Setter CommandEndTxn CommandEndTxn Word64 Word64
-> Word64 -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxn
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxn -> Bool -> Parser CommandEndTxn
loop
(Setter CommandEndTxn CommandEndTxn Word64 Word64
-> Word64 -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxn
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxn -> Bool -> Parser CommandEndTxn
loop
(Setter CommandEndTxn CommandEndTxn Word64 Word64
-> Word64 -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxn
x)
Bool
required'requestId
32
-> do TxnAction
y <- Parser TxnAction -> String -> Parser TxnAction
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> TxnAction) -> Parser Int -> Parser TxnAction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> TxnAction
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"txn_action"
CommandEndTxn -> Bool -> Parser CommandEndTxn
loop
(Setter CommandEndTxn CommandEndTxn TxnAction TxnAction
-> TxnAction -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnAction") TxnAction
y CommandEndTxn
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxn -> Bool -> Parser CommandEndTxn
loop
(Setter CommandEndTxn CommandEndTxn FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandEndTxn -> CommandEndTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandEndTxn CommandEndTxn FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxn
x)
Bool
required'requestId
in
Parser CommandEndTxn -> String -> Parser CommandEndTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxn -> Bool -> Parser CommandEndTxn
loop CommandEndTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "CommandEndTxn"
buildMessage :: CommandEndTxn -> Builder
buildMessage
= \ _x :: CommandEndTxn
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandEndTxn CommandEndTxn Word64 Word64
-> CommandEndTxn -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxn
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxn
CommandEndTxn
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxn
CommandEndTxn
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe TxnAction)
CommandEndTxn
CommandEndTxn
(Maybe TxnAction)
(Maybe TxnAction)
-> CommandEndTxn -> Maybe TxnAction
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction") CommandEndTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: TxnAction
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (TxnAction -> Int) -> TxnAction -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
TxnAction -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
TxnAction
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandEndTxn CommandEndTxn FieldSet FieldSet
-> CommandEndTxn -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandEndTxn CommandEndTxn FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxn
_x)))))
instance Control.DeepSeq.NFData CommandEndTxn where
rnf :: CommandEndTxn -> ()
rnf
= \ x__ :: CommandEndTxn
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxn -> FieldSet
_CommandEndTxn'_unknownFields CommandEndTxn
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxn -> Word64
_CommandEndTxn'requestId CommandEndTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidLeastBits CommandEndTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxn -> Maybe Word64
_CommandEndTxn'txnidMostBits CommandEndTxn
x__)
(Maybe TxnAction -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandEndTxn -> Maybe TxnAction
_CommandEndTxn'txnAction CommandEndTxn
x__) ()))))
data CommandEndTxnOnPartition
= CommandEndTxnOnPartition'_constructor {CommandEndTxnOnPartition -> Word64
_CommandEndTxnOnPartition'requestId :: !Data.Word.Word64,
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnPartition -> Maybe Text
_CommandEndTxnOnPartition'topic :: !(Prelude.Maybe Data.Text.Text),
CommandEndTxnOnPartition -> Maybe TxnAction
_CommandEndTxnOnPartition'txnAction :: !(Prelude.Maybe TxnAction),
CommandEndTxnOnPartition -> FieldSet
_CommandEndTxnOnPartition'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
(CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> Eq CommandEndTxnOnPartition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c/= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
== :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c== :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
Prelude.Eq, Eq CommandEndTxnOnPartition
Eq CommandEndTxnOnPartition =>
(CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Ordering)
-> (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> (CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool)
-> (CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition)
-> (CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition)
-> Ord CommandEndTxnOnPartition
CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Ordering
CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
$cmin :: CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
max :: CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
$cmax :: CommandEndTxnOnPartition
-> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
>= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c>= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
> :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c> :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
<= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c<= :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
< :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
$c< :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Bool
compare :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Ordering
$ccompare :: CommandEndTxnOnPartition -> CommandEndTxnOnPartition -> Ordering
$cp1Ord :: Eq CommandEndTxnOnPartition
Prelude.Ord)
instance Prelude.Show CommandEndTxnOnPartition where
showsPrec :: Int -> CommandEndTxnOnPartition -> ShowS
showsPrec _ __x :: CommandEndTxnOnPartition
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxnOnPartition -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxnOnPartition
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Word64 -> f Word64)
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Word64)
-> (CommandEndTxnOnPartition -> Word64 -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition CommandEndTxnOnPartition Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Word64
_CommandEndTxnOnPartition'requestId
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Word64
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'requestId :: Word64
_CommandEndTxnOnPartition'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Word64)
-> (CommandEndTxnOnPartition
-> Maybe Word64 -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Word64)
-> (CommandEndTxnOnPartition
-> Maybe Word64 -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Word64)
-> (CommandEndTxnOnPartition
-> Maybe Word64 -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Word64)
-> (CommandEndTxnOnPartition
-> Maybe Word64 -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Text)
-> (CommandEndTxnOnPartition
-> Maybe Text -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Text
_CommandEndTxnOnPartition'topic
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Text
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'topic :: Maybe Text
_CommandEndTxnOnPartition'topic = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "maybe'topic" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'topic"
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe Text)
-> (CommandEndTxnOnPartition
-> Maybe Text -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe Text
_CommandEndTxnOnPartition'topic
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe Text
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'topic :: Maybe Text
_CommandEndTxnOnPartition'topic = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "txnAction" TxnAction where
fieldOf :: Proxy# "txnAction"
-> (TxnAction -> f TxnAction)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((TxnAction -> f TxnAction)
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (TxnAction -> f TxnAction)
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe TxnAction)
-> (CommandEndTxnOnPartition
-> Maybe TxnAction -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe TxnAction)
(Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe TxnAction
_CommandEndTxnOnPartition'txnAction
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnAction :: Maybe TxnAction
_CommandEndTxnOnPartition'txnAction = Maybe TxnAction
y__}))
(TxnAction -> Lens' (Maybe TxnAction) TxnAction
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens TxnAction
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartition "maybe'txnAction" (Prelude.Maybe TxnAction) where
fieldOf :: Proxy# "maybe'txnAction"
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnPartition -> f CommandEndTxnOnPartition)
-> ((Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnPartition
-> f CommandEndTxnOnPartition
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartition -> Maybe TxnAction)
-> (CommandEndTxnOnPartition
-> Maybe TxnAction -> CommandEndTxnOnPartition)
-> Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe TxnAction)
(Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> Maybe TxnAction
_CommandEndTxnOnPartition'txnAction
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'txnAction :: Maybe TxnAction
_CommandEndTxnOnPartition'txnAction = Maybe TxnAction
y__}))
(Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxnOnPartition where
messageName :: Proxy CommandEndTxnOnPartition -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxnOnPartition"
packedMessageDescriptor :: Proxy CommandEndTxnOnPartition -> ByteString
packedMessageDescriptor _
= "\n\
\\CANCommandEndTxnOnPartition\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2\DC4\n\
\\ENQtopic\CAN\EOT \SOH(\tR\ENQtopic\DC26\n\
\\n\
\txn_action\CAN\ENQ \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction"
packedFileDescriptor :: Proxy CommandEndTxnOnPartition -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxnOnPartition)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxnOnPartition
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartition Word64
-> FieldDescriptor CommandEndTxnOnPartition
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandEndTxnOnPartition CommandEndTxnOnPartition Word64 Word64
-> FieldAccessor CommandEndTxnOnPartition Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartition
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxnOnPartition
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartition Word64
-> FieldDescriptor CommandEndTxnOnPartition
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnPartition Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartition
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxnOnPartition
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartition Word64
-> FieldDescriptor CommandEndTxnOnPartition
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnPartition Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartition
topic__field_descriptor :: FieldDescriptor CommandEndTxnOnPartition
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandEndTxnOnPartition Text
-> FieldDescriptor CommandEndTxnOnPartition
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandEndTxnOnPartition Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'topic")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartition
txnAction__field_descriptor :: FieldDescriptor CommandEndTxnOnPartition
txnAction__field_descriptor
= String
-> FieldTypeDescriptor TxnAction
-> FieldAccessor CommandEndTxnOnPartition TxnAction
-> FieldDescriptor CommandEndTxnOnPartition
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txn_action"
(ScalarField TxnAction -> FieldTypeDescriptor TxnAction
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField TxnAction
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor TxnAction)
(Lens
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe TxnAction)
(Maybe TxnAction)
-> FieldAccessor CommandEndTxnOnPartition TxnAction
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartition
in
[(Tag, FieldDescriptor CommandEndTxnOnPartition)]
-> Map Tag (FieldDescriptor CommandEndTxnOnPartition)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxnOnPartition
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxnOnPartition
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxnOnPartition
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxnOnPartition
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandEndTxnOnPartition
txnAction__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxnOnPartition FieldSet
unknownFields
= (CommandEndTxnOnPartition -> FieldSet)
-> (CommandEndTxnOnPartition
-> FieldSet -> CommandEndTxnOnPartition)
-> Lens' CommandEndTxnOnPartition FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartition -> FieldSet
_CommandEndTxnOnPartition'_unknownFields
(\ x__ :: CommandEndTxnOnPartition
x__ y__ :: FieldSet
y__ -> CommandEndTxnOnPartition
x__ {_CommandEndTxnOnPartition'_unknownFields :: FieldSet
_CommandEndTxnOnPartition'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxnOnPartition
defMessage
= $WCommandEndTxnOnPartition'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe Text
-> Maybe TxnAction
-> FieldSet
-> CommandEndTxnOnPartition
CommandEndTxnOnPartition'_constructor
{_CommandEndTxnOnPartition'requestId :: Word64
_CommandEndTxnOnPartition'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxnOnPartition'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartition'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartition'topic :: Maybe Text
_CommandEndTxnOnPartition'topic = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartition'txnAction :: Maybe TxnAction
_CommandEndTxnOnPartition'txnAction = Maybe TxnAction
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartition'_unknownFields :: FieldSet
_CommandEndTxnOnPartition'_unknownFields = []}
parseMessage :: Parser CommandEndTxnOnPartition
parseMessage
= let
loop ::
CommandEndTxnOnPartition
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxnOnPartition
loop :: CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop x :: CommandEndTxnOnPartition
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxnOnPartition -> Parser CommandEndTxnOnPartition
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnPartition
-> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxnOnPartition
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition Word64 Word64
-> Word64 -> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxnOnPartition
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition Word64 Word64
-> Word64 -> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxnOnPartition
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition Word64 Word64
-> Word64 -> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxnOnPartition
x)
Bool
required'requestId
34
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter CommandEndTxnOnPartition CommandEndTxnOnPartition Text Text
-> Text -> CommandEndTxnOnPartition -> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandEndTxnOnPartition
x)
Bool
required'requestId
40
-> do TxnAction
y <- Parser TxnAction -> String -> Parser TxnAction
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> TxnAction) -> Parser Int -> Parser TxnAction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> TxnAction
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"txn_action"
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter
CommandEndTxnOnPartition
CommandEndTxnOnPartition
TxnAction
TxnAction
-> TxnAction
-> CommandEndTxnOnPartition
-> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnAction") TxnAction
y CommandEndTxnOnPartition
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop
(Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnPartition
-> CommandEndTxnOnPartition
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnPartition CommandEndTxnOnPartition FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxnOnPartition
x)
Bool
required'requestId
in
Parser CommandEndTxnOnPartition
-> String -> Parser CommandEndTxnOnPartition
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxnOnPartition -> Bool -> Parser CommandEndTxnOnPartition
loop CommandEndTxnOnPartition
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandEndTxnOnPartition"
buildMessage :: CommandEndTxnOnPartition -> Builder
buildMessage
= \ _x :: CommandEndTxnOnPartition
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandEndTxnOnPartition
CommandEndTxnOnPartition
Word64
Word64
-> CommandEndTxnOnPartition -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxnOnPartition
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnPartition -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxnOnPartition
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnPartition -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxnOnPartition
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe Text)
(Maybe Text)
-> CommandEndTxnOnPartition -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'topic") CommandEndTxnOnPartition
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe TxnAction)
CommandEndTxnOnPartition
CommandEndTxnOnPartition
(Maybe TxnAction)
(Maybe TxnAction)
-> CommandEndTxnOnPartition -> Maybe TxnAction
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction") CommandEndTxnOnPartition
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: TxnAction
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
((Int -> Builder) -> (TxnAction -> Int) -> TxnAction -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
TxnAction -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
TxnAction
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandEndTxnOnPartition
CommandEndTxnOnPartition
FieldSet
FieldSet
-> CommandEndTxnOnPartition -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandEndTxnOnPartition
CommandEndTxnOnPartition
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxnOnPartition
_x))))))
instance Control.DeepSeq.NFData CommandEndTxnOnPartition where
rnf :: CommandEndTxnOnPartition -> ()
rnf
= \ x__ :: CommandEndTxnOnPartition
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> FieldSet
_CommandEndTxnOnPartition'_unknownFields CommandEndTxnOnPartition
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> Word64
_CommandEndTxnOnPartition'requestId CommandEndTxnOnPartition
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidLeastBits CommandEndTxnOnPartition
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> Maybe Word64
_CommandEndTxnOnPartition'txnidMostBits CommandEndTxnOnPartition
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> Maybe Text
_CommandEndTxnOnPartition'topic CommandEndTxnOnPartition
x__)
(Maybe TxnAction -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartition -> Maybe TxnAction
_CommandEndTxnOnPartition'txnAction CommandEndTxnOnPartition
x__) ())))))
data CommandEndTxnOnPartitionResponse
= CommandEndTxnOnPartitionResponse'_constructor {CommandEndTxnOnPartitionResponse -> Word64
_CommandEndTxnOnPartitionResponse'requestId :: !Data.Word.Word64,
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnPartitionResponse -> Maybe ServerError
_CommandEndTxnOnPartitionResponse'error :: !(Prelude.Maybe ServerError),
CommandEndTxnOnPartitionResponse -> Maybe Text
_CommandEndTxnOnPartitionResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandEndTxnOnPartitionResponse -> FieldSet
_CommandEndTxnOnPartitionResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
(CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> Eq CommandEndTxnOnPartitionResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c/= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
== :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c== :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
Prelude.Eq, Eq CommandEndTxnOnPartitionResponse
Eq CommandEndTxnOnPartitionResponse =>
(CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Ordering)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse)
-> (CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse)
-> Ord CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Ordering
CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
$cmin :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
max :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
$cmax :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
>= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c>= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
> :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c> :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
<= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c<= :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
< :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
$c< :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Bool
compare :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Ordering
$ccompare :: CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse -> Ordering
$cp1Ord :: Eq CommandEndTxnOnPartitionResponse
Prelude.Ord)
instance Prelude.Show CommandEndTxnOnPartitionResponse where
showsPrec :: Int -> CommandEndTxnOnPartitionResponse -> ShowS
showsPrec _ __x :: CommandEndTxnOnPartitionResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxnOnPartitionResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxnOnPartitionResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Word64)
-> (CommandEndTxnOnPartitionResponse
-> Word64 -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Word64
_CommandEndTxnOnPartitionResponse'requestId
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Word64
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'requestId :: Word64
_CommandEndTxnOnPartitionResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Word64)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Word64 -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Word64)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Word64 -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Word64)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Word64 -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Word64)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Word64 -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe ServerError)
-> (CommandEndTxnOnPartitionResponse
-> Maybe ServerError -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe ServerError
_CommandEndTxnOnPartitionResponse'error
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe ServerError
y__ -> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'error :: Maybe ServerError
_CommandEndTxnOnPartitionResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe ServerError)
-> (CommandEndTxnOnPartitionResponse
-> Maybe ServerError -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe ServerError
_CommandEndTxnOnPartitionResponse'error
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe ServerError
y__ -> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'error :: Maybe ServerError
_CommandEndTxnOnPartitionResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Text)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Text -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Text
_CommandEndTxnOnPartitionResponse'message
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Text
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'message :: Maybe Text
_CommandEndTxnOnPartitionResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnPartitionResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnPartitionResponse
-> f CommandEndTxnOnPartitionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnPartitionResponse -> Maybe Text)
-> (CommandEndTxnOnPartitionResponse
-> Maybe Text -> CommandEndTxnOnPartitionResponse)
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> Maybe Text
_CommandEndTxnOnPartitionResponse'message
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: Maybe Text
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'message :: Maybe Text
_CommandEndTxnOnPartitionResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxnOnPartitionResponse where
messageName :: Proxy CommandEndTxnOnPartitionResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxnOnPartitionResponse"
packedMessageDescriptor :: Proxy CommandEndTxnOnPartitionResponse -> ByteString
packedMessageDescriptor _
= "\n\
\ CommandEndTxnOnPartitionResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandEndTxnOnPartitionResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxnOnPartitionResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxnOnPartitionResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
-> FieldDescriptor CommandEndTxnOnPartitionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartitionResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxnOnPartitionResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
-> FieldDescriptor CommandEndTxnOnPartitionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartitionResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxnOnPartitionResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
-> FieldDescriptor CommandEndTxnOnPartitionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnPartitionResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartitionResponse
error__field_descriptor :: FieldDescriptor CommandEndTxnOnPartitionResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandEndTxnOnPartitionResponse ServerError
-> FieldDescriptor CommandEndTxnOnPartitionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandEndTxnOnPartitionResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartitionResponse
message__field_descriptor :: FieldDescriptor CommandEndTxnOnPartitionResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandEndTxnOnPartitionResponse Text
-> FieldDescriptor CommandEndTxnOnPartitionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandEndTxnOnPartitionResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnPartitionResponse
in
[(Tag, FieldDescriptor CommandEndTxnOnPartitionResponse)]
-> Map Tag (FieldDescriptor CommandEndTxnOnPartitionResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxnOnPartitionResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxnOnPartitionResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxnOnPartitionResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxnOnPartitionResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandEndTxnOnPartitionResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxnOnPartitionResponse FieldSet
unknownFields
= (CommandEndTxnOnPartitionResponse -> FieldSet)
-> (CommandEndTxnOnPartitionResponse
-> FieldSet -> CommandEndTxnOnPartitionResponse)
-> Lens' CommandEndTxnOnPartitionResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnPartitionResponse -> FieldSet
_CommandEndTxnOnPartitionResponse'_unknownFields
(\ x__ :: CommandEndTxnOnPartitionResponse
x__ y__ :: FieldSet
y__
-> CommandEndTxnOnPartitionResponse
x__ {_CommandEndTxnOnPartitionResponse'_unknownFields :: FieldSet
_CommandEndTxnOnPartitionResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxnOnPartitionResponse
defMessage
= $WCommandEndTxnOnPartitionResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse'_constructor
{_CommandEndTxnOnPartitionResponse'requestId :: Word64
_CommandEndTxnOnPartitionResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxnOnPartitionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartitionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartitionResponse'error :: Maybe ServerError
_CommandEndTxnOnPartitionResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartitionResponse'message :: Maybe Text
_CommandEndTxnOnPartitionResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnPartitionResponse'_unknownFields :: FieldSet
_CommandEndTxnOnPartitionResponse'_unknownFields = []}
parseMessage :: Parser CommandEndTxnOnPartitionResponse
parseMessage
= let
loop ::
CommandEndTxnOnPartitionResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxnOnPartitionResponse
loop :: CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop x :: CommandEndTxnOnPartitionResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxnOnPartitionResponse
-> Parser CommandEndTxnOnPartitionResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxnOnPartitionResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxnOnPartitionResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxnOnPartitionResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxnOnPartitionResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
ServerError
ServerError
-> ServerError
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandEndTxnOnPartitionResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Text
Text
-> Text
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandEndTxnOnPartitionResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop
(Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnPartitionResponse
-> CommandEndTxnOnPartitionResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxnOnPartitionResponse
x)
Bool
required'requestId
in
Parser CommandEndTxnOnPartitionResponse
-> String -> Parser CommandEndTxnOnPartitionResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxnOnPartitionResponse
-> Bool -> Parser CommandEndTxnOnPartitionResponse
loop CommandEndTxnOnPartitionResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandEndTxnOnPartitionResponse"
buildMessage :: CommandEndTxnOnPartitionResponse -> Builder
buildMessage
= \ _x :: CommandEndTxnOnPartitionResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
Word64
Word64
-> CommandEndTxnOnPartitionResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxnOnPartitionResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnPartitionResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxnOnPartitionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnPartitionResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxnOnPartitionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandEndTxnOnPartitionResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandEndTxnOnPartitionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
(Maybe Text)
(Maybe Text)
-> CommandEndTxnOnPartitionResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandEndTxnOnPartitionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
-> CommandEndTxnOnPartitionResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandEndTxnOnPartitionResponse
CommandEndTxnOnPartitionResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxnOnPartitionResponse
_x))))))
instance Control.DeepSeq.NFData CommandEndTxnOnPartitionResponse where
rnf :: CommandEndTxnOnPartitionResponse -> ()
rnf
= \ x__ :: CommandEndTxnOnPartitionResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> FieldSet
_CommandEndTxnOnPartitionResponse'_unknownFields CommandEndTxnOnPartitionResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> Word64
_CommandEndTxnOnPartitionResponse'requestId CommandEndTxnOnPartitionResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidLeastBits CommandEndTxnOnPartitionResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> Maybe Word64
_CommandEndTxnOnPartitionResponse'txnidMostBits CommandEndTxnOnPartitionResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> Maybe ServerError
_CommandEndTxnOnPartitionResponse'error CommandEndTxnOnPartitionResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnPartitionResponse -> Maybe Text
_CommandEndTxnOnPartitionResponse'message CommandEndTxnOnPartitionResponse
x__) ())))))
data CommandEndTxnOnSubscription
= CommandEndTxnOnSubscription'_constructor {CommandEndTxnOnSubscription -> Word64
_CommandEndTxnOnSubscription'requestId :: !Data.Word.Word64,
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnSubscription -> Maybe Subscription
_CommandEndTxnOnSubscription'subscription :: !(Prelude.Maybe Subscription),
CommandEndTxnOnSubscription -> Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction :: !(Prelude.Maybe TxnAction),
CommandEndTxnOnSubscription -> FieldSet
_CommandEndTxnOnSubscription'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
(CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> Eq CommandEndTxnOnSubscription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c/= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
== :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c== :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
Prelude.Eq, Eq CommandEndTxnOnSubscription
Eq CommandEndTxnOnSubscription =>
(CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Ordering)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Bool)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription)
-> (CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription)
-> Ord CommandEndTxnOnSubscription
CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Ordering
CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription
$cmin :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription
max :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription
$cmax :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription
>= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c>= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
> :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c> :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
<= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c<= :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
< :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
$c< :: CommandEndTxnOnSubscription -> CommandEndTxnOnSubscription -> Bool
compare :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Ordering
$ccompare :: CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription -> Ordering
$cp1Ord :: Eq CommandEndTxnOnSubscription
Prelude.Ord)
instance Prelude.Show CommandEndTxnOnSubscription where
showsPrec :: Int -> CommandEndTxnOnSubscription -> ShowS
showsPrec _ __x :: CommandEndTxnOnSubscription
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxnOnSubscription -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxnOnSubscription
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Word64 -> f Word64)
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Word64)
-> (CommandEndTxnOnSubscription
-> Word64 -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Word64
_CommandEndTxnOnSubscription'requestId
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Word64
y__ -> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'requestId :: Word64
_CommandEndTxnOnSubscription'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Word64)
-> (CommandEndTxnOnSubscription
-> Maybe Word64 -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Word64)
-> (CommandEndTxnOnSubscription
-> Maybe Word64 -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Word64)
-> (CommandEndTxnOnSubscription
-> Maybe Word64 -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Word64)
-> (CommandEndTxnOnSubscription
-> Maybe Word64 -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "subscription" Subscription where
fieldOf :: Proxy# "subscription"
-> (Subscription -> f Subscription)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Subscription -> f (Maybe Subscription))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Subscription -> f Subscription)
-> Maybe Subscription -> f (Maybe Subscription))
-> (Subscription -> f Subscription)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Subscription)
-> (CommandEndTxnOnSubscription
-> Maybe Subscription -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Subscription)
(Maybe Subscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Subscription
_CommandEndTxnOnSubscription'subscription
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Subscription
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'subscription :: Maybe Subscription
_CommandEndTxnOnSubscription'subscription = Maybe Subscription
y__}))
(Subscription -> Lens' (Maybe Subscription) Subscription
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Subscription
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "maybe'subscription" (Prelude.Maybe Subscription) where
fieldOf :: Proxy# "maybe'subscription"
-> (Maybe Subscription -> f (Maybe Subscription))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe Subscription -> f (Maybe Subscription))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Maybe Subscription -> f (Maybe Subscription))
-> Maybe Subscription -> f (Maybe Subscription))
-> (Maybe Subscription -> f (Maybe Subscription))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe Subscription)
-> (CommandEndTxnOnSubscription
-> Maybe Subscription -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Subscription)
(Maybe Subscription)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe Subscription
_CommandEndTxnOnSubscription'subscription
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe Subscription
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'subscription :: Maybe Subscription
_CommandEndTxnOnSubscription'subscription = Maybe Subscription
y__}))
(Maybe Subscription -> f (Maybe Subscription))
-> Maybe Subscription -> f (Maybe Subscription)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "txnAction" TxnAction where
fieldOf :: Proxy# "txnAction"
-> (TxnAction -> f TxnAction)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((TxnAction -> f TxnAction)
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (TxnAction -> f TxnAction)
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe TxnAction)
-> (CommandEndTxnOnSubscription
-> Maybe TxnAction -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe TxnAction)
(Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnAction :: Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction = Maybe TxnAction
y__}))
(TxnAction -> Lens' (Maybe TxnAction) TxnAction
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens TxnAction
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscription "maybe'txnAction" (Prelude.Maybe TxnAction) where
fieldOf :: Proxy# "maybe'txnAction"
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
fieldOf _
= ((Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnSubscription -> f CommandEndTxnOnSubscription)
-> ((Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction))
-> (Maybe TxnAction -> f (Maybe TxnAction))
-> CommandEndTxnOnSubscription
-> f CommandEndTxnOnSubscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscription -> Maybe TxnAction)
-> (CommandEndTxnOnSubscription
-> Maybe TxnAction -> CommandEndTxnOnSubscription)
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe TxnAction)
(Maybe TxnAction)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: Maybe TxnAction
y__ -> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'txnAction :: Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction = Maybe TxnAction
y__}))
(Maybe TxnAction -> f (Maybe TxnAction))
-> Maybe TxnAction -> f (Maybe TxnAction)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxnOnSubscription where
messageName :: Proxy CommandEndTxnOnSubscription -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxnOnSubscription"
packedMessageDescriptor :: Proxy CommandEndTxnOnSubscription -> ByteString
packedMessageDescriptor _
= "\n\
\\ESCCommandEndTxnOnSubscription\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2>\n\
\\fsubscription\CAN\EOT \SOH(\v2\SUB.pulsar.proto.SubscriptionR\fsubscription\DC26\n\
\\n\
\txn_action\CAN\ENQ \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction"
packedFileDescriptor :: Proxy CommandEndTxnOnSubscription -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxnOnSubscription)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscription
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscription Word64
-> FieldDescriptor CommandEndTxnOnSubscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
-> FieldAccessor CommandEndTxnOnSubscription Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscription
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscription
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscription Word64
-> FieldDescriptor CommandEndTxnOnSubscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnSubscription Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscription
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscription
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscription Word64
-> FieldDescriptor CommandEndTxnOnSubscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnSubscription Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscription
subscription__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscription
subscription__field_descriptor
= String
-> FieldTypeDescriptor Subscription
-> FieldAccessor CommandEndTxnOnSubscription Subscription
-> FieldDescriptor CommandEndTxnOnSubscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subscription"
(MessageOrGroup -> FieldTypeDescriptor Subscription
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Subscription)
(Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Subscription)
(Maybe Subscription)
-> FieldAccessor CommandEndTxnOnSubscription Subscription
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'subscription")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscription
txnAction__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscription
txnAction__field_descriptor
= String
-> FieldTypeDescriptor TxnAction
-> FieldAccessor CommandEndTxnOnSubscription TxnAction
-> FieldDescriptor CommandEndTxnOnSubscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txn_action"
(ScalarField TxnAction -> FieldTypeDescriptor TxnAction
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField TxnAction
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor TxnAction)
(Lens
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe TxnAction)
(Maybe TxnAction)
-> FieldAccessor CommandEndTxnOnSubscription TxnAction
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscription
in
[(Tag, FieldDescriptor CommandEndTxnOnSubscription)]
-> Map Tag (FieldDescriptor CommandEndTxnOnSubscription)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxnOnSubscription
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxnOnSubscription
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxnOnSubscription
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxnOnSubscription
subscription__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandEndTxnOnSubscription
txnAction__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxnOnSubscription FieldSet
unknownFields
= (CommandEndTxnOnSubscription -> FieldSet)
-> (CommandEndTxnOnSubscription
-> FieldSet -> CommandEndTxnOnSubscription)
-> Lens' CommandEndTxnOnSubscription FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscription -> FieldSet
_CommandEndTxnOnSubscription'_unknownFields
(\ x__ :: CommandEndTxnOnSubscription
x__ y__ :: FieldSet
y__
-> CommandEndTxnOnSubscription
x__ {_CommandEndTxnOnSubscription'_unknownFields :: FieldSet
_CommandEndTxnOnSubscription'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxnOnSubscription
defMessage
= $WCommandEndTxnOnSubscription'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe Subscription
-> Maybe TxnAction
-> FieldSet
-> CommandEndTxnOnSubscription
CommandEndTxnOnSubscription'_constructor
{_CommandEndTxnOnSubscription'requestId :: Word64
_CommandEndTxnOnSubscription'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxnOnSubscription'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscription'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscription'subscription :: Maybe Subscription
_CommandEndTxnOnSubscription'subscription = Maybe Subscription
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscription'txnAction :: Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction = Maybe TxnAction
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscription'_unknownFields :: FieldSet
_CommandEndTxnOnSubscription'_unknownFields = []}
parseMessage :: Parser CommandEndTxnOnSubscription
parseMessage
= let
loop ::
CommandEndTxnOnSubscription
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxnOnSubscription
loop :: CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop x :: CommandEndTxnOnSubscription
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxnOnSubscription -> Parser CommandEndTxnOnSubscription
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxnOnSubscription
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxnOnSubscription
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxnOnSubscription
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxnOnSubscription
x)
Bool
required'requestId
34
-> do Subscription
y <- Parser Subscription -> String -> Parser Subscription
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Subscription -> Parser Subscription
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Subscription
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"subscription"
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Subscription
Subscription
-> Subscription
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription") Subscription
y CommandEndTxnOnSubscription
x)
Bool
required'requestId
40
-> do TxnAction
y <- Parser TxnAction -> String -> Parser TxnAction
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> TxnAction) -> Parser Int -> Parser TxnAction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> TxnAction
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"txn_action"
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
TxnAction
TxnAction
-> TxnAction
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnAction") TxnAction
y CommandEndTxnOnSubscription
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop
(Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnSubscription
-> CommandEndTxnOnSubscription
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxnOnSubscription
x)
Bool
required'requestId
in
Parser CommandEndTxnOnSubscription
-> String -> Parser CommandEndTxnOnSubscription
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxnOnSubscription
-> Bool -> Parser CommandEndTxnOnSubscription
loop CommandEndTxnOnSubscription
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandEndTxnOnSubscription"
buildMessage :: CommandEndTxnOnSubscription -> Builder
buildMessage
= \ _x :: CommandEndTxnOnSubscription
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
Word64
Word64
-> CommandEndTxnOnSubscription -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxnOnSubscription
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnSubscription -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxnOnSubscription
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnSubscription -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxnOnSubscription
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Subscription)
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe Subscription)
(Maybe Subscription)
-> CommandEndTxnOnSubscription -> Maybe Subscription
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'subscription") CommandEndTxnOnSubscription
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Subscription
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder)
-> (Subscription -> ByteString) -> Subscription -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Subscription -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Subscription
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe TxnAction)
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
(Maybe TxnAction)
(Maybe TxnAction)
-> CommandEndTxnOnSubscription -> Maybe TxnAction
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnAction" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnAction") CommandEndTxnOnSubscription
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: TxnAction
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
((Int -> Builder) -> (TxnAction -> Int) -> TxnAction -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
TxnAction -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
TxnAction
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
-> CommandEndTxnOnSubscription -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandEndTxnOnSubscription
CommandEndTxnOnSubscription
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxnOnSubscription
_x))))))
instance Control.DeepSeq.NFData CommandEndTxnOnSubscription where
rnf :: CommandEndTxnOnSubscription -> ()
rnf
= \ x__ :: CommandEndTxnOnSubscription
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> FieldSet
_CommandEndTxnOnSubscription'_unknownFields CommandEndTxnOnSubscription
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> Word64
_CommandEndTxnOnSubscription'requestId CommandEndTxnOnSubscription
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidLeastBits CommandEndTxnOnSubscription
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> Maybe Word64
_CommandEndTxnOnSubscription'txnidMostBits CommandEndTxnOnSubscription
x__)
(Maybe Subscription -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> Maybe Subscription
_CommandEndTxnOnSubscription'subscription CommandEndTxnOnSubscription
x__)
(Maybe TxnAction -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscription -> Maybe TxnAction
_CommandEndTxnOnSubscription'txnAction CommandEndTxnOnSubscription
x__) ())))))
data CommandEndTxnOnSubscriptionResponse
= CommandEndTxnOnSubscriptionResponse'_constructor {CommandEndTxnOnSubscriptionResponse -> Word64
_CommandEndTxnOnSubscriptionResponse'requestId :: !Data.Word.Word64,
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnOnSubscriptionResponse -> Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error :: !(Prelude.Maybe ServerError),
CommandEndTxnOnSubscriptionResponse -> Maybe Text
_CommandEndTxnOnSubscriptionResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandEndTxnOnSubscriptionResponse -> FieldSet
_CommandEndTxnOnSubscriptionResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
(CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> Eq CommandEndTxnOnSubscriptionResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c/= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
== :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c== :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
Prelude.Eq, Eq CommandEndTxnOnSubscriptionResponse
Eq CommandEndTxnOnSubscriptionResponse =>
(CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Ordering)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse)
-> (CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse)
-> Ord CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Ordering
CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
$cmin :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
max :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
$cmax :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
>= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c>= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
> :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c> :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
<= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c<= :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
< :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
$c< :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Bool
compare :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Ordering
$ccompare :: CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse -> Ordering
$cp1Ord :: Eq CommandEndTxnOnSubscriptionResponse
Prelude.Ord)
instance Prelude.Show CommandEndTxnOnSubscriptionResponse where
showsPrec :: Int -> CommandEndTxnOnSubscriptionResponse -> ShowS
showsPrec _ __x :: CommandEndTxnOnSubscriptionResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxnOnSubscriptionResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxnOnSubscriptionResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Word64)
-> (CommandEndTxnOnSubscriptionResponse
-> Word64 -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Word64
_CommandEndTxnOnSubscriptionResponse'requestId
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Word64
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'requestId :: Word64
_CommandEndTxnOnSubscriptionResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Word64)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Word64 -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscriptionResponse
x__
{_CommandEndTxnOnSubscriptionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Word64)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Word64 -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscriptionResponse
x__
{_CommandEndTxnOnSubscriptionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Word64)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Word64 -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Word64)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Word64 -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Word64
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe ServerError)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe ServerError -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe ServerError
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'error :: Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe ServerError)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe ServerError -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe ServerError
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'error :: Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Text)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Text -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Text
_CommandEndTxnOnSubscriptionResponse'message
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Text
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'message :: Maybe Text
_CommandEndTxnOnSubscriptionResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnOnSubscriptionResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnOnSubscriptionResponse
-> f CommandEndTxnOnSubscriptionResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnOnSubscriptionResponse -> Maybe Text)
-> (CommandEndTxnOnSubscriptionResponse
-> Maybe Text -> CommandEndTxnOnSubscriptionResponse)
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> Maybe Text
_CommandEndTxnOnSubscriptionResponse'message
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: Maybe Text
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'message :: Maybe Text
_CommandEndTxnOnSubscriptionResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxnOnSubscriptionResponse where
messageName :: Proxy CommandEndTxnOnSubscriptionResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxnOnSubscriptionResponse"
packedMessageDescriptor :: Proxy CommandEndTxnOnSubscriptionResponse -> ByteString
packedMessageDescriptor _
= "\n\
\#CommandEndTxnOnSubscriptionResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandEndTxnOnSubscriptionResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxnOnSubscriptionResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscriptionResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
-> FieldDescriptor CommandEndTxnOnSubscriptionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
-> FieldDescriptor CommandEndTxnOnSubscriptionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
-> FieldDescriptor CommandEndTxnOnSubscriptionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscriptionResponse
error__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscriptionResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandEndTxnOnSubscriptionResponse ServerError
-> FieldDescriptor CommandEndTxnOnSubscriptionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandEndTxnOnSubscriptionResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscriptionResponse
message__field_descriptor :: FieldDescriptor CommandEndTxnOnSubscriptionResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Text
-> FieldDescriptor CommandEndTxnOnSubscriptionResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandEndTxnOnSubscriptionResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnOnSubscriptionResponse
in
[(Tag, FieldDescriptor CommandEndTxnOnSubscriptionResponse)]
-> Map Tag (FieldDescriptor CommandEndTxnOnSubscriptionResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxnOnSubscriptionResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxnOnSubscriptionResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxnOnSubscriptionResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandEndTxnOnSubscriptionResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxnOnSubscriptionResponse FieldSet
unknownFields
= (CommandEndTxnOnSubscriptionResponse -> FieldSet)
-> (CommandEndTxnOnSubscriptionResponse
-> FieldSet -> CommandEndTxnOnSubscriptionResponse)
-> Lens' CommandEndTxnOnSubscriptionResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnOnSubscriptionResponse -> FieldSet
_CommandEndTxnOnSubscriptionResponse'_unknownFields
(\ x__ :: CommandEndTxnOnSubscriptionResponse
x__ y__ :: FieldSet
y__
-> CommandEndTxnOnSubscriptionResponse
x__ {_CommandEndTxnOnSubscriptionResponse'_unknownFields :: FieldSet
_CommandEndTxnOnSubscriptionResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxnOnSubscriptionResponse
defMessage
= $WCommandEndTxnOnSubscriptionResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse'_constructor
{_CommandEndTxnOnSubscriptionResponse'requestId :: Word64
_CommandEndTxnOnSubscriptionResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscriptionResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscriptionResponse'error :: Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscriptionResponse'message :: Maybe Text
_CommandEndTxnOnSubscriptionResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnOnSubscriptionResponse'_unknownFields :: FieldSet
_CommandEndTxnOnSubscriptionResponse'_unknownFields = []}
parseMessage :: Parser CommandEndTxnOnSubscriptionResponse
parseMessage
= let
loop ::
CommandEndTxnOnSubscriptionResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxnOnSubscriptionResponse
loop :: CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop x :: CommandEndTxnOnSubscriptionResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxnOnSubscriptionResponse
-> Parser CommandEndTxnOnSubscriptionResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxnOnSubscriptionResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxnOnSubscriptionResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxnOnSubscriptionResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
-> Word64
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxnOnSubscriptionResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
ServerError
ServerError
-> ServerError
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandEndTxnOnSubscriptionResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Text
Text
-> Text
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandEndTxnOnSubscriptionResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop
(Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnOnSubscriptionResponse
-> CommandEndTxnOnSubscriptionResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxnOnSubscriptionResponse
x)
Bool
required'requestId
in
Parser CommandEndTxnOnSubscriptionResponse
-> String -> Parser CommandEndTxnOnSubscriptionResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxnOnSubscriptionResponse
-> Bool -> Parser CommandEndTxnOnSubscriptionResponse
loop CommandEndTxnOnSubscriptionResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandEndTxnOnSubscriptionResponse"
buildMessage :: CommandEndTxnOnSubscriptionResponse -> Builder
buildMessage
= \ _x :: CommandEndTxnOnSubscriptionResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
Word64
Word64
-> CommandEndTxnOnSubscriptionResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxnOnSubscriptionResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnSubscriptionResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxnOnSubscriptionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnOnSubscriptionResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxnOnSubscriptionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandEndTxnOnSubscriptionResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandEndTxnOnSubscriptionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
(Maybe Text)
(Maybe Text)
-> CommandEndTxnOnSubscriptionResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandEndTxnOnSubscriptionResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
-> CommandEndTxnOnSubscriptionResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandEndTxnOnSubscriptionResponse
CommandEndTxnOnSubscriptionResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxnOnSubscriptionResponse
_x))))))
instance Control.DeepSeq.NFData CommandEndTxnOnSubscriptionResponse where
rnf :: CommandEndTxnOnSubscriptionResponse -> ()
rnf
= \ x__ :: CommandEndTxnOnSubscriptionResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> FieldSet
_CommandEndTxnOnSubscriptionResponse'_unknownFields CommandEndTxnOnSubscriptionResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> Word64
_CommandEndTxnOnSubscriptionResponse'requestId CommandEndTxnOnSubscriptionResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidLeastBits CommandEndTxnOnSubscriptionResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> Maybe Word64
_CommandEndTxnOnSubscriptionResponse'txnidMostBits CommandEndTxnOnSubscriptionResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> Maybe ServerError
_CommandEndTxnOnSubscriptionResponse'error CommandEndTxnOnSubscriptionResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnOnSubscriptionResponse -> Maybe Text
_CommandEndTxnOnSubscriptionResponse'message CommandEndTxnOnSubscriptionResponse
x__) ())))))
data CommandEndTxnResponse
= CommandEndTxnResponse'_constructor {CommandEndTxnResponse -> Word64
_CommandEndTxnResponse'requestId :: !Data.Word.Word64,
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandEndTxnResponse -> Maybe ServerError
_CommandEndTxnResponse'error :: !(Prelude.Maybe ServerError),
CommandEndTxnResponse -> Maybe Text
_CommandEndTxnResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandEndTxnResponse -> FieldSet
_CommandEndTxnResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
(CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> Eq CommandEndTxnResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c/= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
== :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c== :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
Prelude.Eq, Eq CommandEndTxnResponse
Eq CommandEndTxnResponse =>
(CommandEndTxnResponse -> CommandEndTxnResponse -> Ordering)
-> (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> (CommandEndTxnResponse -> CommandEndTxnResponse -> Bool)
-> (CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse)
-> (CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse)
-> Ord CommandEndTxnResponse
CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
CommandEndTxnResponse -> CommandEndTxnResponse -> Ordering
CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse
$cmin :: CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse
max :: CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse
$cmax :: CommandEndTxnResponse
-> CommandEndTxnResponse -> CommandEndTxnResponse
>= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c>= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
> :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c> :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
<= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c<= :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
< :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
$c< :: CommandEndTxnResponse -> CommandEndTxnResponse -> Bool
compare :: CommandEndTxnResponse -> CommandEndTxnResponse -> Ordering
$ccompare :: CommandEndTxnResponse -> CommandEndTxnResponse -> Ordering
$cp1Ord :: Eq CommandEndTxnResponse
Prelude.Ord)
instance Prelude.Show CommandEndTxnResponse where
showsPrec :: Int -> CommandEndTxnResponse -> ShowS
showsPrec _ __x :: CommandEndTxnResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandEndTxnResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandEndTxnResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Word64)
-> (CommandEndTxnResponse -> Word64 -> CommandEndTxnResponse)
-> Lens CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Word64
_CommandEndTxnResponse'requestId
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Word64
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'requestId :: Word64
_CommandEndTxnResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Word64)
-> (CommandEndTxnResponse -> Maybe Word64 -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidLeastBits
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Word64)
-> (CommandEndTxnResponse -> Maybe Word64 -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidLeastBits
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Word64)
-> (CommandEndTxnResponse -> Maybe Word64 -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidMostBits
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Word64)
-> (CommandEndTxnResponse -> Maybe Word64 -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidMostBits
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe ServerError)
-> (CommandEndTxnResponse
-> Maybe ServerError -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe ServerError
_CommandEndTxnResponse'error
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'error :: Maybe ServerError
_CommandEndTxnResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe ServerError)
-> (CommandEndTxnResponse
-> Maybe ServerError -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe ServerError
_CommandEndTxnResponse'error
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'error :: Maybe ServerError
_CommandEndTxnResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Text)
-> (CommandEndTxnResponse -> Maybe Text -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Text
_CommandEndTxnResponse'message
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Text
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'message :: Maybe Text
_CommandEndTxnResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandEndTxnResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandEndTxnResponse -> f CommandEndTxnResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandEndTxnResponse
-> f CommandEndTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandEndTxnResponse -> Maybe Text)
-> (CommandEndTxnResponse -> Maybe Text -> CommandEndTxnResponse)
-> Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> Maybe Text
_CommandEndTxnResponse'message
(\ x__ :: CommandEndTxnResponse
x__ y__ :: Maybe Text
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'message :: Maybe Text
_CommandEndTxnResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandEndTxnResponse where
messageName :: Proxy CommandEndTxnResponse -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandEndTxnResponse"
packedMessageDescriptor :: Proxy CommandEndTxnResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\NAKCommandEndTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandEndTxnResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandEndTxnResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandEndTxnResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnResponse Word64
-> FieldDescriptor CommandEndTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
-> FieldAccessor CommandEndTxnResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandEndTxnResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnResponse Word64
-> FieldDescriptor CommandEndTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandEndTxnResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandEndTxnResponse Word64
-> FieldDescriptor CommandEndTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandEndTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnResponse
error__field_descriptor :: FieldDescriptor CommandEndTxnResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandEndTxnResponse ServerError
-> FieldDescriptor CommandEndTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandEndTxnResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnResponse
message__field_descriptor :: FieldDescriptor CommandEndTxnResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandEndTxnResponse Text
-> FieldDescriptor CommandEndTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandEndTxnResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandEndTxnResponse
in
[(Tag, FieldDescriptor CommandEndTxnResponse)]
-> Map Tag (FieldDescriptor CommandEndTxnResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandEndTxnResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandEndTxnResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandEndTxnResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandEndTxnResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandEndTxnResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandEndTxnResponse FieldSet
unknownFields
= (CommandEndTxnResponse -> FieldSet)
-> (CommandEndTxnResponse -> FieldSet -> CommandEndTxnResponse)
-> Lens' CommandEndTxnResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandEndTxnResponse -> FieldSet
_CommandEndTxnResponse'_unknownFields
(\ x__ :: CommandEndTxnResponse
x__ y__ :: FieldSet
y__ -> CommandEndTxnResponse
x__ {_CommandEndTxnResponse'_unknownFields :: FieldSet
_CommandEndTxnResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandEndTxnResponse
defMessage
= $WCommandEndTxnResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandEndTxnResponse
CommandEndTxnResponse'_constructor
{_CommandEndTxnResponse'requestId :: Word64
_CommandEndTxnResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandEndTxnResponse'txnidLeastBits :: Maybe Word64
_CommandEndTxnResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnResponse'txnidMostBits :: Maybe Word64
_CommandEndTxnResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnResponse'error :: Maybe ServerError
_CommandEndTxnResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnResponse'message :: Maybe Text
_CommandEndTxnResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandEndTxnResponse'_unknownFields :: FieldSet
_CommandEndTxnResponse'_unknownFields = []}
parseMessage :: Parser CommandEndTxnResponse
parseMessage
= let
loop ::
CommandEndTxnResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandEndTxnResponse
loop :: CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop x :: CommandEndTxnResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandEndTxnResponse -> Parser CommandEndTxnResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandEndTxnResponse CommandEndTxnResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnResponse
-> CommandEndTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnResponse CommandEndTxnResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandEndTxnResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
-> Word64 -> CommandEndTxnResponse -> CommandEndTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandEndTxnResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
-> Word64 -> CommandEndTxnResponse -> CommandEndTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandEndTxnResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
-> Word64 -> CommandEndTxnResponse -> CommandEndTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandEndTxnResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter
CommandEndTxnResponse CommandEndTxnResponse ServerError ServerError
-> ServerError -> CommandEndTxnResponse -> CommandEndTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandEndTxnResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter CommandEndTxnResponse CommandEndTxnResponse Text Text
-> Text -> CommandEndTxnResponse -> CommandEndTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandEndTxnResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop
(Setter
CommandEndTxnResponse CommandEndTxnResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandEndTxnResponse
-> CommandEndTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandEndTxnResponse CommandEndTxnResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandEndTxnResponse
x)
Bool
required'requestId
in
Parser CommandEndTxnResponse
-> String -> Parser CommandEndTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandEndTxnResponse -> Bool -> Parser CommandEndTxnResponse
loop CommandEndTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandEndTxnResponse"
buildMessage :: CommandEndTxnResponse -> Builder
buildMessage
= \ _x :: CommandEndTxnResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandEndTxnResponse CommandEndTxnResponse Word64 Word64
-> CommandEndTxnResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandEndTxnResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandEndTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandEndTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandEndTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandEndTxnResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandEndTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandEndTxnResponse
CommandEndTxnResponse
(Maybe Text)
(Maybe Text)
-> CommandEndTxnResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandEndTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandEndTxnResponse
CommandEndTxnResponse
FieldSet
FieldSet
-> CommandEndTxnResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandEndTxnResponse
CommandEndTxnResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandEndTxnResponse
_x))))))
instance Control.DeepSeq.NFData CommandEndTxnResponse where
rnf :: CommandEndTxnResponse -> ()
rnf
= \ x__ :: CommandEndTxnResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> FieldSet
_CommandEndTxnResponse'_unknownFields CommandEndTxnResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> Word64
_CommandEndTxnResponse'requestId CommandEndTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidLeastBits CommandEndTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> Maybe Word64
_CommandEndTxnResponse'txnidMostBits CommandEndTxnResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> Maybe ServerError
_CommandEndTxnResponse'error CommandEndTxnResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandEndTxnResponse -> Maybe Text
_CommandEndTxnResponse'message CommandEndTxnResponse
x__) ())))))
data CommandError
= CommandError'_constructor {CommandError -> Word64
_CommandError'requestId :: !Data.Word.Word64,
CommandError -> ServerError
_CommandError'error :: !ServerError,
CommandError -> Text
_CommandError'message :: !Data.Text.Text,
CommandError -> FieldSet
_CommandError'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandError -> CommandError -> Bool
(CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool) -> Eq CommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandError -> CommandError -> Bool
$c/= :: CommandError -> CommandError -> Bool
== :: CommandError -> CommandError -> Bool
$c== :: CommandError -> CommandError -> Bool
Prelude.Eq, Eq CommandError
Eq CommandError =>
(CommandError -> CommandError -> Ordering)
-> (CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> CommandError)
-> (CommandError -> CommandError -> CommandError)
-> Ord CommandError
CommandError -> CommandError -> Bool
CommandError -> CommandError -> Ordering
CommandError -> CommandError -> CommandError
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandError -> CommandError -> CommandError
$cmin :: CommandError -> CommandError -> CommandError
max :: CommandError -> CommandError -> CommandError
$cmax :: CommandError -> CommandError -> CommandError
>= :: CommandError -> CommandError -> Bool
$c>= :: CommandError -> CommandError -> Bool
> :: CommandError -> CommandError -> Bool
$c> :: CommandError -> CommandError -> Bool
<= :: CommandError -> CommandError -> Bool
$c<= :: CommandError -> CommandError -> Bool
< :: CommandError -> CommandError -> Bool
$c< :: CommandError -> CommandError -> Bool
compare :: CommandError -> CommandError -> Ordering
$ccompare :: CommandError -> CommandError -> Ordering
$cp1Ord :: Eq CommandError
Prelude.Ord)
instance Prelude.Show CommandError where
showsPrec :: Int -> CommandError -> ShowS
showsPrec _ __x :: CommandError
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandError -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandError
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandError "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandError -> f CommandError
fieldOf _
= ((Word64 -> f Word64) -> CommandError -> f CommandError)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandError
-> f CommandError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandError -> Word64)
-> (CommandError -> Word64 -> CommandError)
-> Lens CommandError CommandError Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandError -> Word64
_CommandError'requestId
(\ x__ :: CommandError
x__ y__ :: Word64
y__ -> CommandError
x__ {_CommandError'requestId :: Word64
_CommandError'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandError "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError) -> CommandError -> f CommandError
fieldOf _
= ((ServerError -> f ServerError) -> CommandError -> f CommandError)
-> ((ServerError -> f ServerError) -> ServerError -> f ServerError)
-> (ServerError -> f ServerError)
-> CommandError
-> f CommandError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandError -> ServerError)
-> (CommandError -> ServerError -> CommandError)
-> Lens CommandError CommandError ServerError ServerError
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandError -> ServerError
_CommandError'error (\ x__ :: CommandError
x__ y__ :: ServerError
y__ -> CommandError
x__ {_CommandError'error :: ServerError
_CommandError'error = ServerError
y__}))
(ServerError -> f ServerError) -> ServerError -> f ServerError
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandError "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text) -> CommandError -> f CommandError
fieldOf _
= ((Text -> f Text) -> CommandError -> f CommandError)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandError
-> f CommandError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandError -> Text)
-> (CommandError -> Text -> CommandError)
-> Lens CommandError CommandError Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandError -> Text
_CommandError'message
(\ x__ :: CommandError
x__ y__ :: Text
y__ -> CommandError
x__ {_CommandError'message :: Text
_CommandError'message = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandError where
messageName :: Proxy CommandError -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandError"
packedMessageDescriptor :: Proxy CommandError -> ByteString
packedMessageDescriptor _
= "\n\
\\fCommandError\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2/\n\
\\ENQerror\CAN\STX \STX(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ETX \STX(\tR\amessage"
packedFileDescriptor :: Proxy CommandError -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandError)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandError
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandError Word64
-> FieldDescriptor CommandError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandError CommandError Word64 Word64
-> FieldAccessor CommandError Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandError
error__field_descriptor :: FieldDescriptor CommandError
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandError ServerError
-> FieldDescriptor CommandError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(WireDefault ServerError
-> Lens CommandError CommandError ServerError ServerError
-> FieldAccessor CommandError ServerError
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ServerError
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error")) ::
Data.ProtoLens.FieldDescriptor CommandError
message__field_descriptor :: FieldDescriptor CommandError
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandError Text
-> FieldDescriptor CommandError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandError CommandError Text Text
-> FieldAccessor CommandError Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message")) ::
Data.ProtoLens.FieldDescriptor CommandError
in
[(Tag, FieldDescriptor CommandError)]
-> Map Tag (FieldDescriptor CommandError)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandError
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandError
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandError
message__field_descriptor)]
unknownFields :: LensLike' f CommandError FieldSet
unknownFields
= (CommandError -> FieldSet)
-> (CommandError -> FieldSet -> CommandError)
-> Lens' CommandError FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandError -> FieldSet
_CommandError'_unknownFields
(\ x__ :: CommandError
x__ y__ :: FieldSet
y__ -> CommandError
x__ {_CommandError'_unknownFields :: FieldSet
_CommandError'_unknownFields = FieldSet
y__})
defMessage :: CommandError
defMessage
= $WCommandError'_constructor :: Word64 -> ServerError -> Text -> FieldSet -> CommandError
CommandError'_constructor
{_CommandError'requestId :: Word64
_CommandError'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandError'error :: ServerError
_CommandError'error = ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandError'message :: Text
_CommandError'message = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandError'_unknownFields :: FieldSet
_CommandError'_unknownFields = []}
parseMessage :: Parser CommandError
parseMessage
= let
loop ::
CommandError
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandError
loop :: CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop x :: CommandError
x required'error :: Bool
required'error required'message :: Bool
required'message required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'error then (:) "error" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'message then (:) "message" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandError -> Parser CommandError
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandError CommandError FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandError -> CommandError
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandError CommandError FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandError
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop
(Setter CommandError CommandError Word64 Word64
-> Word64 -> CommandError -> CommandError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandError
x)
Bool
required'error
Bool
required'message
Bool
Prelude.False
16
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop
(Setter CommandError CommandError ServerError ServerError
-> ServerError -> CommandError -> CommandError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandError
x)
Bool
Prelude.False
Bool
required'message
Bool
required'requestId
26
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop
(Setter CommandError CommandError Text Text
-> Text -> CommandError -> CommandError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandError
x)
Bool
required'error
Bool
Prelude.False
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop
(Setter CommandError CommandError FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandError -> CommandError
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandError CommandError FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandError
x)
Bool
required'error
Bool
required'message
Bool
required'requestId
in
Parser CommandError -> String -> Parser CommandError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandError -> Bool -> Bool -> Bool -> Parser CommandError
loop
CommandError
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True Bool
Prelude.True)
"CommandError"
buildMessage :: CommandError -> Builder
buildMessage
= \ _x :: CommandError
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandError CommandError Word64 Word64
-> CommandError -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandError
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
ServerError CommandError CommandError ServerError ServerError
-> CommandError -> ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") CommandError
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandError CommandError Text Text
-> CommandError -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") CommandError
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandError CommandError FieldSet FieldSet
-> CommandError -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandError CommandError FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandError
_x))))
instance Control.DeepSeq.NFData CommandError where
rnf :: CommandError -> ()
rnf
= \ x__ :: CommandError
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandError -> FieldSet
_CommandError'_unknownFields CommandError
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandError -> Word64
_CommandError'requestId CommandError
x__)
(ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandError -> ServerError
_CommandError'error CommandError
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandError -> Text
_CommandError'message CommandError
x__) ())))
data CommandFlow
= CommandFlow'_constructor {CommandFlow -> Word64
_CommandFlow'consumerId :: !Data.Word.Word64,
CommandFlow -> Word32
_CommandFlow'messagePermits :: !Data.Word.Word32,
CommandFlow -> FieldSet
_CommandFlow'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandFlow -> CommandFlow -> Bool
(CommandFlow -> CommandFlow -> Bool)
-> (CommandFlow -> CommandFlow -> Bool) -> Eq CommandFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandFlow -> CommandFlow -> Bool
$c/= :: CommandFlow -> CommandFlow -> Bool
== :: CommandFlow -> CommandFlow -> Bool
$c== :: CommandFlow -> CommandFlow -> Bool
Prelude.Eq, Eq CommandFlow
Eq CommandFlow =>
(CommandFlow -> CommandFlow -> Ordering)
-> (CommandFlow -> CommandFlow -> Bool)
-> (CommandFlow -> CommandFlow -> Bool)
-> (CommandFlow -> CommandFlow -> Bool)
-> (CommandFlow -> CommandFlow -> Bool)
-> (CommandFlow -> CommandFlow -> CommandFlow)
-> (CommandFlow -> CommandFlow -> CommandFlow)
-> Ord CommandFlow
CommandFlow -> CommandFlow -> Bool
CommandFlow -> CommandFlow -> Ordering
CommandFlow -> CommandFlow -> CommandFlow
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandFlow -> CommandFlow -> CommandFlow
$cmin :: CommandFlow -> CommandFlow -> CommandFlow
max :: CommandFlow -> CommandFlow -> CommandFlow
$cmax :: CommandFlow -> CommandFlow -> CommandFlow
>= :: CommandFlow -> CommandFlow -> Bool
$c>= :: CommandFlow -> CommandFlow -> Bool
> :: CommandFlow -> CommandFlow -> Bool
$c> :: CommandFlow -> CommandFlow -> Bool
<= :: CommandFlow -> CommandFlow -> Bool
$c<= :: CommandFlow -> CommandFlow -> Bool
< :: CommandFlow -> CommandFlow -> Bool
$c< :: CommandFlow -> CommandFlow -> Bool
compare :: CommandFlow -> CommandFlow -> Ordering
$ccompare :: CommandFlow -> CommandFlow -> Ordering
$cp1Ord :: Eq CommandFlow
Prelude.Ord)
instance Prelude.Show CommandFlow where
showsPrec :: Int -> CommandFlow -> ShowS
showsPrec _ __x :: CommandFlow
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandFlow -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandFlow
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandFlow "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64) -> CommandFlow -> f CommandFlow
fieldOf _
= ((Word64 -> f Word64) -> CommandFlow -> f CommandFlow)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandFlow
-> f CommandFlow
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandFlow -> Word64)
-> (CommandFlow -> Word64 -> CommandFlow)
-> Lens CommandFlow CommandFlow Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandFlow -> Word64
_CommandFlow'consumerId
(\ x__ :: CommandFlow
x__ y__ :: Word64
y__ -> CommandFlow
x__ {_CommandFlow'consumerId :: Word64
_CommandFlow'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandFlow "messagePermits" Data.Word.Word32 where
fieldOf :: Proxy# "messagePermits"
-> (Word32 -> f Word32) -> CommandFlow -> f CommandFlow
fieldOf _
= ((Word32 -> f Word32) -> CommandFlow -> f CommandFlow)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> CommandFlow
-> f CommandFlow
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandFlow -> Word32)
-> (CommandFlow -> Word32 -> CommandFlow)
-> Lens CommandFlow CommandFlow Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandFlow -> Word32
_CommandFlow'messagePermits
(\ x__ :: CommandFlow
x__ y__ :: Word32
y__ -> CommandFlow
x__ {_CommandFlow'messagePermits :: Word32
_CommandFlow'messagePermits = Word32
y__}))
(Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandFlow where
messageName :: Proxy CommandFlow -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandFlow"
packedMessageDescriptor :: Proxy CommandFlow -> ByteString
packedMessageDescriptor _
= "\n\
\\vCommandFlow\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2&\n\
\\SOmessagePermits\CAN\STX \STX(\rR\SOmessagePermits"
packedFileDescriptor :: Proxy CommandFlow -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandFlow)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandFlow
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandFlow Word64
-> FieldDescriptor CommandFlow
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandFlow CommandFlow Word64 Word64
-> FieldAccessor CommandFlow Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandFlow
messagePermits__field_descriptor :: FieldDescriptor CommandFlow
messagePermits__field_descriptor
= String
-> FieldTypeDescriptor Word32
-> FieldAccessor CommandFlow Word32
-> FieldDescriptor CommandFlow
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"messagePermits"
(ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
(WireDefault Word32
-> Lens CommandFlow CommandFlow Word32 Word32
-> FieldAccessor CommandFlow Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word32
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "messagePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messagePermits")) ::
Data.ProtoLens.FieldDescriptor CommandFlow
in
[(Tag, FieldDescriptor CommandFlow)]
-> Map Tag (FieldDescriptor CommandFlow)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandFlow
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandFlow
messagePermits__field_descriptor)]
unknownFields :: LensLike' f CommandFlow FieldSet
unknownFields
= (CommandFlow -> FieldSet)
-> (CommandFlow -> FieldSet -> CommandFlow)
-> Lens' CommandFlow FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandFlow -> FieldSet
_CommandFlow'_unknownFields
(\ x__ :: CommandFlow
x__ y__ :: FieldSet
y__ -> CommandFlow
x__ {_CommandFlow'_unknownFields :: FieldSet
_CommandFlow'_unknownFields = FieldSet
y__})
defMessage :: CommandFlow
defMessage
= $WCommandFlow'_constructor :: Word64 -> Word32 -> FieldSet -> CommandFlow
CommandFlow'_constructor
{_CommandFlow'consumerId :: Word64
_CommandFlow'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandFlow'messagePermits :: Word32
_CommandFlow'messagePermits = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandFlow'_unknownFields :: FieldSet
_CommandFlow'_unknownFields = []}
parseMessage :: Parser CommandFlow
parseMessage
= let
loop ::
CommandFlow
-> Prelude.Bool
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser CommandFlow
loop :: CommandFlow -> Bool -> Bool -> Parser CommandFlow
loop x :: CommandFlow
x required'consumerId :: Bool
required'consumerId required'messagePermits :: Bool
required'messagePermits
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'messagePermits then
(:) "messagePermits"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
[])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandFlow -> Parser CommandFlow
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandFlow CommandFlow FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandFlow -> CommandFlow
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandFlow CommandFlow FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandFlow
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandFlow -> Bool -> Bool -> Parser CommandFlow
loop
(Setter CommandFlow CommandFlow Word64 Word64
-> Word64 -> CommandFlow -> CommandFlow
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandFlow
x)
Bool
Prelude.False
Bool
required'messagePermits
16
-> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"messagePermits"
CommandFlow -> Bool -> Bool -> Parser CommandFlow
loop
(Setter CommandFlow CommandFlow Word32 Word32
-> Word32 -> CommandFlow -> CommandFlow
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "messagePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messagePermits") Word32
y CommandFlow
x)
Bool
required'consumerId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandFlow -> Bool -> Bool -> Parser CommandFlow
loop
(Setter CommandFlow CommandFlow FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandFlow -> CommandFlow
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandFlow CommandFlow FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandFlow
x)
Bool
required'consumerId
Bool
required'messagePermits
in
Parser CommandFlow -> String -> Parser CommandFlow
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandFlow -> Bool -> Bool -> Parser CommandFlow
loop CommandFlow
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandFlow"
buildMessage :: CommandFlow -> Builder
buildMessage
= \ _x :: CommandFlow
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandFlow CommandFlow Word64 Word64
-> CommandFlow -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandFlow
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(FoldLike Word32 CommandFlow CommandFlow Word32 Word32
-> CommandFlow -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "messagePermits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messagePermits") CommandFlow
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandFlow CommandFlow FieldSet FieldSet
-> CommandFlow -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandFlow CommandFlow FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandFlow
_x)))
instance Control.DeepSeq.NFData CommandFlow where
rnf :: CommandFlow -> ()
rnf
= \ x__ :: CommandFlow
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandFlow -> FieldSet
_CommandFlow'_unknownFields CommandFlow
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandFlow -> Word64
_CommandFlow'consumerId CommandFlow
x__)
(Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandFlow -> Word32
_CommandFlow'messagePermits CommandFlow
x__) ()))
data CommandGetLastMessageId
= CommandGetLastMessageId'_constructor {CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'consumerId :: !Data.Word.Word64,
CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'requestId :: !Data.Word.Word64,
CommandGetLastMessageId -> FieldSet
_CommandGetLastMessageId'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
(CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> Eq CommandGetLastMessageId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c/= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
== :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c== :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
Prelude.Eq, Eq CommandGetLastMessageId
Eq CommandGetLastMessageId =>
(CommandGetLastMessageId -> CommandGetLastMessageId -> Ordering)
-> (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> (CommandGetLastMessageId -> CommandGetLastMessageId -> Bool)
-> (CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId)
-> (CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId)
-> Ord CommandGetLastMessageId
CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
CommandGetLastMessageId -> CommandGetLastMessageId -> Ordering
CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId
$cmin :: CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId
max :: CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId
$cmax :: CommandGetLastMessageId
-> CommandGetLastMessageId -> CommandGetLastMessageId
>= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c>= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
> :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c> :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
<= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c<= :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
< :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
$c< :: CommandGetLastMessageId -> CommandGetLastMessageId -> Bool
compare :: CommandGetLastMessageId -> CommandGetLastMessageId -> Ordering
$ccompare :: CommandGetLastMessageId -> CommandGetLastMessageId -> Ordering
$cp1Ord :: Eq CommandGetLastMessageId
Prelude.Ord)
instance Prelude.Show CommandGetLastMessageId where
showsPrec :: Int -> CommandGetLastMessageId -> ShowS
showsPrec _ __x :: CommandGetLastMessageId
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetLastMessageId -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetLastMessageId
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetLastMessageId "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandGetLastMessageId
-> f CommandGetLastMessageId
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetLastMessageId -> f CommandGetLastMessageId)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetLastMessageId
-> f CommandGetLastMessageId
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetLastMessageId -> Word64)
-> (CommandGetLastMessageId -> Word64 -> CommandGetLastMessageId)
-> Lens
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'consumerId
(\ x__ :: CommandGetLastMessageId
x__ y__ :: Word64
y__ -> CommandGetLastMessageId
x__ {_CommandGetLastMessageId'consumerId :: Word64
_CommandGetLastMessageId'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetLastMessageId "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetLastMessageId
-> f CommandGetLastMessageId
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetLastMessageId -> f CommandGetLastMessageId)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetLastMessageId
-> f CommandGetLastMessageId
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetLastMessageId -> Word64)
-> (CommandGetLastMessageId -> Word64 -> CommandGetLastMessageId)
-> Lens
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'requestId
(\ x__ :: CommandGetLastMessageId
x__ y__ :: Word64
y__ -> CommandGetLastMessageId
x__ {_CommandGetLastMessageId'requestId :: Word64
_CommandGetLastMessageId'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetLastMessageId where
messageName :: Proxy CommandGetLastMessageId -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetLastMessageId"
packedMessageDescriptor :: Proxy CommandGetLastMessageId -> ByteString
packedMessageDescriptor _
= "\n\
\\ETBCommandGetLastMessageId\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId"
packedFileDescriptor :: Proxy CommandGetLastMessageId -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetLastMessageId)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandGetLastMessageId
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetLastMessageId Word64
-> FieldDescriptor CommandGetLastMessageId
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
-> FieldAccessor CommandGetLastMessageId Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandGetLastMessageId
requestId__field_descriptor :: FieldDescriptor CommandGetLastMessageId
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetLastMessageId Word64
-> FieldDescriptor CommandGetLastMessageId
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
-> FieldAccessor CommandGetLastMessageId Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetLastMessageId
in
[(Tag, FieldDescriptor CommandGetLastMessageId)]
-> Map Tag (FieldDescriptor CommandGetLastMessageId)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetLastMessageId
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetLastMessageId
requestId__field_descriptor)]
unknownFields :: LensLike' f CommandGetLastMessageId FieldSet
unknownFields
= (CommandGetLastMessageId -> FieldSet)
-> (CommandGetLastMessageId -> FieldSet -> CommandGetLastMessageId)
-> Lens' CommandGetLastMessageId FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageId -> FieldSet
_CommandGetLastMessageId'_unknownFields
(\ x__ :: CommandGetLastMessageId
x__ y__ :: FieldSet
y__ -> CommandGetLastMessageId
x__ {_CommandGetLastMessageId'_unknownFields :: FieldSet
_CommandGetLastMessageId'_unknownFields = FieldSet
y__})
defMessage :: CommandGetLastMessageId
defMessage
= $WCommandGetLastMessageId'_constructor :: Word64 -> Word64 -> FieldSet -> CommandGetLastMessageId
CommandGetLastMessageId'_constructor
{_CommandGetLastMessageId'consumerId :: Word64
_CommandGetLastMessageId'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetLastMessageId'requestId :: Word64
_CommandGetLastMessageId'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetLastMessageId'_unknownFields :: FieldSet
_CommandGetLastMessageId'_unknownFields = []}
parseMessage :: Parser CommandGetLastMessageId
parseMessage
= let
loop ::
CommandGetLastMessageId
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetLastMessageId
loop :: CommandGetLastMessageId
-> Bool -> Bool -> Parser CommandGetLastMessageId
loop x :: CommandGetLastMessageId
x required'consumerId :: Bool
required'consumerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetLastMessageId -> Parser CommandGetLastMessageId
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetLastMessageId CommandGetLastMessageId FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetLastMessageId
-> CommandGetLastMessageId
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetLastMessageId CommandGetLastMessageId FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetLastMessageId
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandGetLastMessageId
-> Bool -> Bool -> Parser CommandGetLastMessageId
loop
(Setter
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
-> Word64 -> CommandGetLastMessageId -> CommandGetLastMessageId
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandGetLastMessageId
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetLastMessageId
-> Bool -> Bool -> Parser CommandGetLastMessageId
loop
(Setter
CommandGetLastMessageId CommandGetLastMessageId Word64 Word64
-> Word64 -> CommandGetLastMessageId -> CommandGetLastMessageId
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetLastMessageId
x)
Bool
required'consumerId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetLastMessageId
-> Bool -> Bool -> Parser CommandGetLastMessageId
loop
(Setter
CommandGetLastMessageId CommandGetLastMessageId FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetLastMessageId
-> CommandGetLastMessageId
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetLastMessageId CommandGetLastMessageId FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetLastMessageId
x)
Bool
required'consumerId
Bool
required'requestId
in
Parser CommandGetLastMessageId
-> String -> Parser CommandGetLastMessageId
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetLastMessageId
-> Bool -> Bool -> Parser CommandGetLastMessageId
loop CommandGetLastMessageId
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandGetLastMessageId"
buildMessage :: CommandGetLastMessageId -> Builder
buildMessage
= \ _x :: CommandGetLastMessageId
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetLastMessageId
CommandGetLastMessageId
Word64
Word64
-> CommandGetLastMessageId -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandGetLastMessageId
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetLastMessageId
CommandGetLastMessageId
Word64
Word64
-> CommandGetLastMessageId -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetLastMessageId
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetLastMessageId
CommandGetLastMessageId
FieldSet
FieldSet
-> CommandGetLastMessageId -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetLastMessageId
CommandGetLastMessageId
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetLastMessageId
_x)))
instance Control.DeepSeq.NFData CommandGetLastMessageId where
rnf :: CommandGetLastMessageId -> ()
rnf
= \ x__ :: CommandGetLastMessageId
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageId -> FieldSet
_CommandGetLastMessageId'_unknownFields CommandGetLastMessageId
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'consumerId CommandGetLastMessageId
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageId -> Word64
_CommandGetLastMessageId'requestId CommandGetLastMessageId
x__) ()))
data CommandGetLastMessageIdResponse
= CommandGetLastMessageIdResponse'_constructor {CommandGetLastMessageIdResponse -> MessageIdData
_CommandGetLastMessageIdResponse'lastMessageId :: !MessageIdData,
CommandGetLastMessageIdResponse -> Word64
_CommandGetLastMessageIdResponse'requestId :: !Data.Word.Word64,
CommandGetLastMessageIdResponse -> FieldSet
_CommandGetLastMessageIdResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
(CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> Eq CommandGetLastMessageIdResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c/= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
== :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c== :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
Prelude.Eq, Eq CommandGetLastMessageIdResponse
Eq CommandGetLastMessageIdResponse =>
(CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Ordering)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse)
-> (CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse)
-> Ord CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Ordering
CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
$cmin :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
max :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
$cmax :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
>= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c>= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
> :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c> :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
<= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c<= :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
< :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
$c< :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Bool
compare :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Ordering
$ccompare :: CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse -> Ordering
$cp1Ord :: Eq CommandGetLastMessageIdResponse
Prelude.Ord)
instance Prelude.Show CommandGetLastMessageIdResponse where
showsPrec :: Int -> CommandGetLastMessageIdResponse -> ShowS
showsPrec _ __x :: CommandGetLastMessageIdResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetLastMessageIdResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetLastMessageIdResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetLastMessageIdResponse "lastMessageId" MessageIdData where
fieldOf :: Proxy# "lastMessageId"
-> (MessageIdData -> f MessageIdData)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse
fieldOf _
= ((MessageIdData -> f MessageIdData)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse)
-> ((MessageIdData -> f MessageIdData)
-> MessageIdData -> f MessageIdData)
-> (MessageIdData -> f MessageIdData)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetLastMessageIdResponse -> MessageIdData)
-> (CommandGetLastMessageIdResponse
-> MessageIdData -> CommandGetLastMessageIdResponse)
-> Lens
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
MessageIdData
MessageIdData
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageIdResponse -> MessageIdData
_CommandGetLastMessageIdResponse'lastMessageId
(\ x__ :: CommandGetLastMessageIdResponse
x__ y__ :: MessageIdData
y__
-> CommandGetLastMessageIdResponse
x__ {_CommandGetLastMessageIdResponse'lastMessageId :: MessageIdData
_CommandGetLastMessageIdResponse'lastMessageId = MessageIdData
y__}))
(MessageIdData -> f MessageIdData)
-> MessageIdData -> f MessageIdData
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetLastMessageIdResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetLastMessageIdResponse
-> f CommandGetLastMessageIdResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetLastMessageIdResponse -> Word64)
-> (CommandGetLastMessageIdResponse
-> Word64 -> CommandGetLastMessageIdResponse)
-> Lens
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageIdResponse -> Word64
_CommandGetLastMessageIdResponse'requestId
(\ x__ :: CommandGetLastMessageIdResponse
x__ y__ :: Word64
y__
-> CommandGetLastMessageIdResponse
x__ {_CommandGetLastMessageIdResponse'requestId :: Word64
_CommandGetLastMessageIdResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetLastMessageIdResponse where
messageName :: Proxy CommandGetLastMessageIdResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetLastMessageIdResponse"
packedMessageDescriptor :: Proxy CommandGetLastMessageIdResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\USCommandGetLastMessageIdResponse\DC2C\n\
\\SIlast_message_id\CAN\SOH \STX(\v2\ESC.pulsar.proto.MessageIdDataR\rlastMessageId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId"
packedFileDescriptor :: Proxy CommandGetLastMessageIdResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetLastMessageIdResponse)
fieldsByTag
= let
lastMessageId__field_descriptor :: FieldDescriptor CommandGetLastMessageIdResponse
lastMessageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandGetLastMessageIdResponse MessageIdData
-> FieldDescriptor CommandGetLastMessageIdResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"last_message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(WireDefault MessageIdData
-> Lens
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
MessageIdData
MessageIdData
-> FieldAccessor CommandGetLastMessageIdResponse MessageIdData
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault MessageIdData
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "lastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lastMessageId")) ::
Data.ProtoLens.FieldDescriptor CommandGetLastMessageIdResponse
requestId__field_descriptor :: FieldDescriptor CommandGetLastMessageIdResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetLastMessageIdResponse Word64
-> FieldDescriptor CommandGetLastMessageIdResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
Word64
Word64
-> FieldAccessor CommandGetLastMessageIdResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetLastMessageIdResponse
in
[(Tag, FieldDescriptor CommandGetLastMessageIdResponse)]
-> Map Tag (FieldDescriptor CommandGetLastMessageIdResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetLastMessageIdResponse
lastMessageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetLastMessageIdResponse
requestId__field_descriptor)]
unknownFields :: LensLike' f CommandGetLastMessageIdResponse FieldSet
unknownFields
= (CommandGetLastMessageIdResponse -> FieldSet)
-> (CommandGetLastMessageIdResponse
-> FieldSet -> CommandGetLastMessageIdResponse)
-> Lens' CommandGetLastMessageIdResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetLastMessageIdResponse -> FieldSet
_CommandGetLastMessageIdResponse'_unknownFields
(\ x__ :: CommandGetLastMessageIdResponse
x__ y__ :: FieldSet
y__
-> CommandGetLastMessageIdResponse
x__ {_CommandGetLastMessageIdResponse'_unknownFields :: FieldSet
_CommandGetLastMessageIdResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandGetLastMessageIdResponse
defMessage
= $WCommandGetLastMessageIdResponse'_constructor :: MessageIdData
-> Word64 -> FieldSet -> CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse'_constructor
{_CommandGetLastMessageIdResponse'lastMessageId :: MessageIdData
_CommandGetLastMessageIdResponse'lastMessageId = MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage,
_CommandGetLastMessageIdResponse'requestId :: Word64
_CommandGetLastMessageIdResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetLastMessageIdResponse'_unknownFields :: FieldSet
_CommandGetLastMessageIdResponse'_unknownFields = []}
parseMessage :: Parser CommandGetLastMessageIdResponse
parseMessage
= let
loop ::
CommandGetLastMessageIdResponse
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetLastMessageIdResponse
loop :: CommandGetLastMessageIdResponse
-> Bool -> Bool -> Parser CommandGetLastMessageIdResponse
loop x :: CommandGetLastMessageIdResponse
x required'lastMessageId :: Bool
required'lastMessageId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'lastMessageId then
(:) "last_message_id"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetLastMessageIdResponse
-> Parser CommandGetLastMessageIdResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetLastMessageIdResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"last_message_id"
CommandGetLastMessageIdResponse
-> Bool -> Bool -> Parser CommandGetLastMessageIdResponse
loop
(Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
MessageIdData
MessageIdData
-> MessageIdData
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "lastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lastMessageId") MessageIdData
y CommandGetLastMessageIdResponse
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetLastMessageIdResponse
-> Bool -> Bool -> Parser CommandGetLastMessageIdResponse
loop
(Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
Word64
Word64
-> Word64
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetLastMessageIdResponse
x)
Bool
required'lastMessageId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetLastMessageIdResponse
-> Bool -> Bool -> Parser CommandGetLastMessageIdResponse
loop
(Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetLastMessageIdResponse
-> CommandGetLastMessageIdResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetLastMessageIdResponse
x)
Bool
required'lastMessageId
Bool
required'requestId
in
Parser CommandGetLastMessageIdResponse
-> String -> Parser CommandGetLastMessageIdResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetLastMessageIdResponse
-> Bool -> Bool -> Parser CommandGetLastMessageIdResponse
loop CommandGetLastMessageIdResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandGetLastMessageIdResponse"
buildMessage :: CommandGetLastMessageIdResponse -> Builder
buildMessage
= \ _x :: CommandGetLastMessageIdResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
(FoldLike
MessageIdData
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
MessageIdData
MessageIdData
-> CommandGetLastMessageIdResponse -> MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "lastMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lastMessageId") CommandGetLastMessageIdResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
Word64
Word64
-> CommandGetLastMessageIdResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetLastMessageIdResponse
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
-> CommandGetLastMessageIdResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetLastMessageIdResponse
CommandGetLastMessageIdResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetLastMessageIdResponse
_x)))
instance Control.DeepSeq.NFData CommandGetLastMessageIdResponse where
rnf :: CommandGetLastMessageIdResponse -> ()
rnf
= \ x__ :: CommandGetLastMessageIdResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageIdResponse -> FieldSet
_CommandGetLastMessageIdResponse'_unknownFields CommandGetLastMessageIdResponse
x__)
(MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageIdResponse -> MessageIdData
_CommandGetLastMessageIdResponse'lastMessageId CommandGetLastMessageIdResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetLastMessageIdResponse -> Word64
_CommandGetLastMessageIdResponse'requestId CommandGetLastMessageIdResponse
x__) ()))
data CommandGetOrCreateSchema
= CommandGetOrCreateSchema'_constructor {CommandGetOrCreateSchema -> Word64
_CommandGetOrCreateSchema'requestId :: !Data.Word.Word64,
CommandGetOrCreateSchema -> Text
_CommandGetOrCreateSchema'topic :: !Data.Text.Text,
CommandGetOrCreateSchema -> Schema
_CommandGetOrCreateSchema'schema :: !Schema,
CommandGetOrCreateSchema -> FieldSet
_CommandGetOrCreateSchema'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
(CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> Eq CommandGetOrCreateSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c/= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
== :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c== :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
Prelude.Eq, Eq CommandGetOrCreateSchema
Eq CommandGetOrCreateSchema =>
(CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Ordering)
-> (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> (CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool)
-> (CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema)
-> (CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema)
-> Ord CommandGetOrCreateSchema
CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Ordering
CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
$cmin :: CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
max :: CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
$cmax :: CommandGetOrCreateSchema
-> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
>= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c>= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
> :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c> :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
<= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c<= :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
< :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
$c< :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Bool
compare :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Ordering
$ccompare :: CommandGetOrCreateSchema -> CommandGetOrCreateSchema -> Ordering
$cp1Ord :: Eq CommandGetOrCreateSchema
Prelude.Ord)
instance Prelude.Show CommandGetOrCreateSchema where
showsPrec :: Int -> CommandGetOrCreateSchema -> ShowS
showsPrec _ __x :: CommandGetOrCreateSchema
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetOrCreateSchema -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetOrCreateSchema
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchema "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchema -> Word64)
-> (CommandGetOrCreateSchema -> Word64 -> CommandGetOrCreateSchema)
-> Lens
CommandGetOrCreateSchema CommandGetOrCreateSchema Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchema -> Word64
_CommandGetOrCreateSchema'requestId
(\ x__ :: CommandGetOrCreateSchema
x__ y__ :: Word64
y__ -> CommandGetOrCreateSchema
x__ {_CommandGetOrCreateSchema'requestId :: Word64
_CommandGetOrCreateSchema'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchema "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
fieldOf _
= ((Text -> f Text)
-> CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchema -> Text)
-> (CommandGetOrCreateSchema -> Text -> CommandGetOrCreateSchema)
-> Lens CommandGetOrCreateSchema CommandGetOrCreateSchema Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchema -> Text
_CommandGetOrCreateSchema'topic
(\ x__ :: CommandGetOrCreateSchema
x__ y__ :: Text
y__ -> CommandGetOrCreateSchema
x__ {_CommandGetOrCreateSchema'topic :: Text
_CommandGetOrCreateSchema'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchema "schema" Schema where
fieldOf :: Proxy# "schema"
-> (Schema -> f Schema)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
fieldOf _
= ((Schema -> f Schema)
-> CommandGetOrCreateSchema -> f CommandGetOrCreateSchema)
-> ((Schema -> f Schema) -> Schema -> f Schema)
-> (Schema -> f Schema)
-> CommandGetOrCreateSchema
-> f CommandGetOrCreateSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchema -> Schema)
-> (CommandGetOrCreateSchema -> Schema -> CommandGetOrCreateSchema)
-> Lens
CommandGetOrCreateSchema CommandGetOrCreateSchema Schema Schema
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchema -> Schema
_CommandGetOrCreateSchema'schema
(\ x__ :: CommandGetOrCreateSchema
x__ y__ :: Schema
y__ -> CommandGetOrCreateSchema
x__ {_CommandGetOrCreateSchema'schema :: Schema
_CommandGetOrCreateSchema'schema = Schema
y__}))
(Schema -> f Schema) -> Schema -> f Schema
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetOrCreateSchema where
messageName :: Proxy CommandGetOrCreateSchema -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetOrCreateSchema"
packedMessageDescriptor :: Proxy CommandGetOrCreateSchema -> ByteString
packedMessageDescriptor _
= "\n\
\\CANCommandGetOrCreateSchema\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\DC4\n\
\\ENQtopic\CAN\STX \STX(\tR\ENQtopic\DC2,\n\
\\ACKschema\CAN\ETX \STX(\v2\DC4.pulsar.proto.SchemaR\ACKschema"
packedFileDescriptor :: Proxy CommandGetOrCreateSchema -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetOrCreateSchema)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetOrCreateSchema
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetOrCreateSchema Word64
-> FieldDescriptor CommandGetOrCreateSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetOrCreateSchema CommandGetOrCreateSchema Word64 Word64
-> FieldAccessor CommandGetOrCreateSchema Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchema
topic__field_descriptor :: FieldDescriptor CommandGetOrCreateSchema
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetOrCreateSchema Text
-> FieldDescriptor CommandGetOrCreateSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandGetOrCreateSchema CommandGetOrCreateSchema Text Text
-> FieldAccessor CommandGetOrCreateSchema Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchema
schema__field_descriptor :: FieldDescriptor CommandGetOrCreateSchema
schema__field_descriptor
= String
-> FieldTypeDescriptor Schema
-> FieldAccessor CommandGetOrCreateSchema Schema
-> FieldDescriptor CommandGetOrCreateSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema"
(MessageOrGroup -> FieldTypeDescriptor Schema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Schema)
(WireDefault Schema
-> Lens
CommandGetOrCreateSchema CommandGetOrCreateSchema Schema Schema
-> FieldAccessor CommandGetOrCreateSchema Schema
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Schema
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchema
in
[(Tag, FieldDescriptor CommandGetOrCreateSchema)]
-> Map Tag (FieldDescriptor CommandGetOrCreateSchema)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetOrCreateSchema
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetOrCreateSchema
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandGetOrCreateSchema
schema__field_descriptor)]
unknownFields :: LensLike' f CommandGetOrCreateSchema FieldSet
unknownFields
= (CommandGetOrCreateSchema -> FieldSet)
-> (CommandGetOrCreateSchema
-> FieldSet -> CommandGetOrCreateSchema)
-> Lens' CommandGetOrCreateSchema FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchema -> FieldSet
_CommandGetOrCreateSchema'_unknownFields
(\ x__ :: CommandGetOrCreateSchema
x__ y__ :: FieldSet
y__ -> CommandGetOrCreateSchema
x__ {_CommandGetOrCreateSchema'_unknownFields :: FieldSet
_CommandGetOrCreateSchema'_unknownFields = FieldSet
y__})
defMessage :: CommandGetOrCreateSchema
defMessage
= $WCommandGetOrCreateSchema'_constructor :: Word64 -> Text -> Schema -> FieldSet -> CommandGetOrCreateSchema
CommandGetOrCreateSchema'_constructor
{_CommandGetOrCreateSchema'requestId :: Word64
_CommandGetOrCreateSchema'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetOrCreateSchema'topic :: Text
_CommandGetOrCreateSchema'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetOrCreateSchema'schema :: Schema
_CommandGetOrCreateSchema'schema = Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage,
_CommandGetOrCreateSchema'_unknownFields :: FieldSet
_CommandGetOrCreateSchema'_unknownFields = []}
parseMessage :: Parser CommandGetOrCreateSchema
parseMessage
= let
loop ::
CommandGetOrCreateSchema
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetOrCreateSchema
loop :: CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop x :: CommandGetOrCreateSchema
x required'requestId :: Bool
required'requestId required'schema :: Bool
required'schema required'topic :: Bool
required'topic
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'schema then (:) "schema" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) []))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetOrCreateSchema -> Parser CommandGetOrCreateSchema
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetOrCreateSchema
-> CommandGetOrCreateSchema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetOrCreateSchema
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop
(Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema Word64 Word64
-> Word64 -> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetOrCreateSchema
x)
Bool
Prelude.False
Bool
required'schema
Bool
required'topic
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop
(Setter CommandGetOrCreateSchema CommandGetOrCreateSchema Text Text
-> Text -> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandGetOrCreateSchema
x)
Bool
required'requestId
Bool
required'schema
Bool
Prelude.False
26
-> do Schema
y <- Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Schema -> Parser Schema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Schema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"schema"
CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop
(Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema Schema Schema
-> Schema -> CommandGetOrCreateSchema -> CommandGetOrCreateSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") Schema
y CommandGetOrCreateSchema
x)
Bool
required'requestId
Bool
Prelude.False
Bool
required'topic
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop
(Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetOrCreateSchema
-> CommandGetOrCreateSchema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetOrCreateSchema CommandGetOrCreateSchema FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetOrCreateSchema
x)
Bool
required'requestId
Bool
required'schema
Bool
required'topic
in
Parser CommandGetOrCreateSchema
-> String -> Parser CommandGetOrCreateSchema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetOrCreateSchema
-> Bool -> Bool -> Bool -> Parser CommandGetOrCreateSchema
loop
CommandGetOrCreateSchema
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True Bool
Prelude.True)
"CommandGetOrCreateSchema"
buildMessage :: CommandGetOrCreateSchema -> Builder
buildMessage
= \ _x :: CommandGetOrCreateSchema
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetOrCreateSchema
CommandGetOrCreateSchema
Word64
Word64
-> CommandGetOrCreateSchema -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetOrCreateSchema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike
Text CommandGetOrCreateSchema CommandGetOrCreateSchema Text Text
-> CommandGetOrCreateSchema -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandGetOrCreateSchema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (Schema -> ByteString) -> Schema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Schema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
(FoldLike
Schema
CommandGetOrCreateSchema
CommandGetOrCreateSchema
Schema
Schema
-> CommandGetOrCreateSchema -> Schema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") CommandGetOrCreateSchema
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetOrCreateSchema
CommandGetOrCreateSchema
FieldSet
FieldSet
-> CommandGetOrCreateSchema -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetOrCreateSchema
CommandGetOrCreateSchema
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetOrCreateSchema
_x))))
instance Control.DeepSeq.NFData CommandGetOrCreateSchema where
rnf :: CommandGetOrCreateSchema -> ()
rnf
= \ x__ :: CommandGetOrCreateSchema
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchema -> FieldSet
_CommandGetOrCreateSchema'_unknownFields CommandGetOrCreateSchema
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchema -> Word64
_CommandGetOrCreateSchema'requestId CommandGetOrCreateSchema
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchema -> Text
_CommandGetOrCreateSchema'topic CommandGetOrCreateSchema
x__)
(Schema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchema -> Schema
_CommandGetOrCreateSchema'schema CommandGetOrCreateSchema
x__) ())))
data CommandGetOrCreateSchemaResponse
= CommandGetOrCreateSchemaResponse'_constructor {CommandGetOrCreateSchemaResponse -> Word64
_CommandGetOrCreateSchemaResponse'requestId :: !Data.Word.Word64,
CommandGetOrCreateSchemaResponse -> Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode :: !(Prelude.Maybe ServerError),
CommandGetOrCreateSchemaResponse -> Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage :: !(Prelude.Maybe Data.Text.Text),
CommandGetOrCreateSchemaResponse -> Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion :: !(Prelude.Maybe Data.ByteString.ByteString),
CommandGetOrCreateSchemaResponse -> FieldSet
_CommandGetOrCreateSchemaResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
(CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> Eq CommandGetOrCreateSchemaResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c/= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
== :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c== :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
Prelude.Eq, Eq CommandGetOrCreateSchemaResponse
Eq CommandGetOrCreateSchemaResponse =>
(CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Ordering)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse)
-> (CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse)
-> Ord CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Ordering
CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
$cmin :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
max :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
$cmax :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
>= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c>= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
> :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c> :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
<= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c<= :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
< :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
$c< :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Bool
compare :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Ordering
$ccompare :: CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse -> Ordering
$cp1Ord :: Eq CommandGetOrCreateSchemaResponse
Prelude.Ord)
instance Prelude.Show CommandGetOrCreateSchemaResponse where
showsPrec :: Int -> CommandGetOrCreateSchemaResponse -> ShowS
showsPrec _ __x :: CommandGetOrCreateSchemaResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetOrCreateSchemaResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetOrCreateSchemaResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Word64)
-> (CommandGetOrCreateSchemaResponse
-> Word64 -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Word64
_CommandGetOrCreateSchemaResponse'requestId
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Word64
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'requestId :: Word64
_CommandGetOrCreateSchemaResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "errorCode" ServerError where
fieldOf :: Proxy# "errorCode"
-> (ServerError -> f ServerError)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe ServerError)
-> (CommandGetOrCreateSchemaResponse
-> Maybe ServerError -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe ServerError
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'errorCode :: Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "maybe'errorCode" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'errorCode"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe ServerError)
-> (CommandGetOrCreateSchemaResponse
-> Maybe ServerError -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe ServerError
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'errorCode :: Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "errorMessage" Data.Text.Text where
fieldOf :: Proxy# "errorMessage"
-> (Text -> f Text)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe Text)
-> (CommandGetOrCreateSchemaResponse
-> Maybe Text -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe Text
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'errorMessage :: Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "maybe'errorMessage" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'errorMessage"
-> (Maybe Text -> f (Maybe Text))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe Text)
-> (CommandGetOrCreateSchemaResponse
-> Maybe Text -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe Text
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'errorMessage :: Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "schemaVersion" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaVersion"
-> (ByteString -> f ByteString)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe ByteString)
-> (CommandGetOrCreateSchemaResponse
-> Maybe ByteString -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe ByteString
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetOrCreateSchemaResponse "maybe'schemaVersion" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'schemaVersion"
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetOrCreateSchemaResponse
-> f CommandGetOrCreateSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetOrCreateSchemaResponse -> Maybe ByteString)
-> (CommandGetOrCreateSchemaResponse
-> Maybe ByteString -> CommandGetOrCreateSchemaResponse)
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: Maybe ByteString
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetOrCreateSchemaResponse where
messageName :: Proxy CommandGetOrCreateSchemaResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetOrCreateSchemaResponse"
packedMessageDescriptor :: Proxy CommandGetOrCreateSchemaResponse -> ByteString
packedMessageDescriptor _
= "\n\
\ CommandGetOrCreateSchemaResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2%\n\
\\SOschema_version\CAN\EOT \SOH(\fR\rschemaVersion"
packedFileDescriptor :: Proxy CommandGetOrCreateSchemaResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetOrCreateSchemaResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetOrCreateSchemaResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetOrCreateSchemaResponse Word64
-> FieldDescriptor CommandGetOrCreateSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
Word64
Word64
-> FieldAccessor CommandGetOrCreateSchemaResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchemaResponse
errorCode__field_descriptor :: FieldDescriptor CommandGetOrCreateSchemaResponse
errorCode__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandGetOrCreateSchemaResponse ServerError
-> FieldDescriptor CommandGetOrCreateSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_code"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandGetOrCreateSchemaResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchemaResponse
errorMessage__field_descriptor :: FieldDescriptor CommandGetOrCreateSchemaResponse
errorMessage__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetOrCreateSchemaResponse Text
-> FieldDescriptor CommandGetOrCreateSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandGetOrCreateSchemaResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchemaResponse
schemaVersion__field_descriptor :: FieldDescriptor CommandGetOrCreateSchemaResponse
schemaVersion__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor CommandGetOrCreateSchemaResponse ByteString
-> FieldDescriptor CommandGetOrCreateSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_version"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor CommandGetOrCreateSchemaResponse ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion")) ::
Data.ProtoLens.FieldDescriptor CommandGetOrCreateSchemaResponse
in
[(Tag, FieldDescriptor CommandGetOrCreateSchemaResponse)]
-> Map Tag (FieldDescriptor CommandGetOrCreateSchemaResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetOrCreateSchemaResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetOrCreateSchemaResponse
errorCode__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandGetOrCreateSchemaResponse
errorMessage__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandGetOrCreateSchemaResponse
schemaVersion__field_descriptor)]
unknownFields :: LensLike' f CommandGetOrCreateSchemaResponse FieldSet
unknownFields
= (CommandGetOrCreateSchemaResponse -> FieldSet)
-> (CommandGetOrCreateSchemaResponse
-> FieldSet -> CommandGetOrCreateSchemaResponse)
-> Lens' CommandGetOrCreateSchemaResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetOrCreateSchemaResponse -> FieldSet
_CommandGetOrCreateSchemaResponse'_unknownFields
(\ x__ :: CommandGetOrCreateSchemaResponse
x__ y__ :: FieldSet
y__
-> CommandGetOrCreateSchemaResponse
x__ {_CommandGetOrCreateSchemaResponse'_unknownFields :: FieldSet
_CommandGetOrCreateSchemaResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandGetOrCreateSchemaResponse
defMessage
= $WCommandGetOrCreateSchemaResponse'_constructor :: Word64
-> Maybe ServerError
-> Maybe Text
-> Maybe ByteString
-> FieldSet
-> CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse'_constructor
{_CommandGetOrCreateSchemaResponse'requestId :: Word64
_CommandGetOrCreateSchemaResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetOrCreateSchemaResponse'errorCode :: Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandGetOrCreateSchemaResponse'errorMessage :: Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandGetOrCreateSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_CommandGetOrCreateSchemaResponse'_unknownFields :: FieldSet
_CommandGetOrCreateSchemaResponse'_unknownFields = []}
parseMessage :: Parser CommandGetOrCreateSchemaResponse
parseMessage
= let
loop ::
CommandGetOrCreateSchemaResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetOrCreateSchemaResponse
loop :: CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop x :: CommandGetOrCreateSchemaResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetOrCreateSchemaResponse
-> Parser CommandGetOrCreateSchemaResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetOrCreateSchemaResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
Word64
Word64
-> Word64
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetOrCreateSchemaResponse
x)
Bool
Prelude.False
16
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error_code"
CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
ServerError
ServerError
-> ServerError
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorCode") ServerError
y CommandGetOrCreateSchemaResponse
x)
Bool
required'requestId
26
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"error_message"
CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
Text
Text
-> Text
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorMessage") Text
y CommandGetOrCreateSchemaResponse
x)
Bool
required'requestId
34
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_version"
CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
ByteString
ByteString
-> ByteString
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaVersion") ByteString
y CommandGetOrCreateSchemaResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop
(Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetOrCreateSchemaResponse
-> CommandGetOrCreateSchemaResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetOrCreateSchemaResponse
x)
Bool
required'requestId
in
Parser CommandGetOrCreateSchemaResponse
-> String -> Parser CommandGetOrCreateSchemaResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetOrCreateSchemaResponse
-> Bool -> Parser CommandGetOrCreateSchemaResponse
loop CommandGetOrCreateSchemaResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandGetOrCreateSchemaResponse"
buildMessage :: CommandGetOrCreateSchemaResponse -> Builder
buildMessage
= \ _x :: CommandGetOrCreateSchemaResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
Word64
Word64
-> CommandGetOrCreateSchemaResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetOrCreateSchemaResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandGetOrCreateSchemaResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode") CommandGetOrCreateSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe Text)
(Maybe Text)
-> CommandGetOrCreateSchemaResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage") CommandGetOrCreateSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
-> CommandGetOrCreateSchemaResponse -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion") CommandGetOrCreateSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
-> CommandGetOrCreateSchemaResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetOrCreateSchemaResponse
CommandGetOrCreateSchemaResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetOrCreateSchemaResponse
_x)))))
instance Control.DeepSeq.NFData CommandGetOrCreateSchemaResponse where
rnf :: CommandGetOrCreateSchemaResponse -> ()
rnf
= \ x__ :: CommandGetOrCreateSchemaResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchemaResponse -> FieldSet
_CommandGetOrCreateSchemaResponse'_unknownFields CommandGetOrCreateSchemaResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchemaResponse -> Word64
_CommandGetOrCreateSchemaResponse'requestId CommandGetOrCreateSchemaResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchemaResponse -> Maybe ServerError
_CommandGetOrCreateSchemaResponse'errorCode CommandGetOrCreateSchemaResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchemaResponse -> Maybe Text
_CommandGetOrCreateSchemaResponse'errorMessage CommandGetOrCreateSchemaResponse
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetOrCreateSchemaResponse -> Maybe ByteString
_CommandGetOrCreateSchemaResponse'schemaVersion CommandGetOrCreateSchemaResponse
x__) ()))))
data CommandGetSchema
= CommandGetSchema'_constructor {CommandGetSchema -> Word64
_CommandGetSchema'requestId :: !Data.Word.Word64,
CommandGetSchema -> Text
_CommandGetSchema'topic :: !Data.Text.Text,
CommandGetSchema -> Maybe ByteString
_CommandGetSchema'schemaVersion :: !(Prelude.Maybe Data.ByteString.ByteString),
CommandGetSchema -> FieldSet
_CommandGetSchema'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetSchema -> CommandGetSchema -> Bool
(CommandGetSchema -> CommandGetSchema -> Bool)
-> (CommandGetSchema -> CommandGetSchema -> Bool)
-> Eq CommandGetSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetSchema -> CommandGetSchema -> Bool
$c/= :: CommandGetSchema -> CommandGetSchema -> Bool
== :: CommandGetSchema -> CommandGetSchema -> Bool
$c== :: CommandGetSchema -> CommandGetSchema -> Bool
Prelude.Eq, Eq CommandGetSchema
Eq CommandGetSchema =>
(CommandGetSchema -> CommandGetSchema -> Ordering)
-> (CommandGetSchema -> CommandGetSchema -> Bool)
-> (CommandGetSchema -> CommandGetSchema -> Bool)
-> (CommandGetSchema -> CommandGetSchema -> Bool)
-> (CommandGetSchema -> CommandGetSchema -> Bool)
-> (CommandGetSchema -> CommandGetSchema -> CommandGetSchema)
-> (CommandGetSchema -> CommandGetSchema -> CommandGetSchema)
-> Ord CommandGetSchema
CommandGetSchema -> CommandGetSchema -> Bool
CommandGetSchema -> CommandGetSchema -> Ordering
CommandGetSchema -> CommandGetSchema -> CommandGetSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetSchema -> CommandGetSchema -> CommandGetSchema
$cmin :: CommandGetSchema -> CommandGetSchema -> CommandGetSchema
max :: CommandGetSchema -> CommandGetSchema -> CommandGetSchema
$cmax :: CommandGetSchema -> CommandGetSchema -> CommandGetSchema
>= :: CommandGetSchema -> CommandGetSchema -> Bool
$c>= :: CommandGetSchema -> CommandGetSchema -> Bool
> :: CommandGetSchema -> CommandGetSchema -> Bool
$c> :: CommandGetSchema -> CommandGetSchema -> Bool
<= :: CommandGetSchema -> CommandGetSchema -> Bool
$c<= :: CommandGetSchema -> CommandGetSchema -> Bool
< :: CommandGetSchema -> CommandGetSchema -> Bool
$c< :: CommandGetSchema -> CommandGetSchema -> Bool
compare :: CommandGetSchema -> CommandGetSchema -> Ordering
$ccompare :: CommandGetSchema -> CommandGetSchema -> Ordering
$cp1Ord :: Eq CommandGetSchema
Prelude.Ord)
instance Prelude.Show CommandGetSchema where
showsPrec :: Int -> CommandGetSchema -> ShowS
showsPrec _ __x :: CommandGetSchema
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetSchema -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetSchema
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetSchema "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandGetSchema -> f CommandGetSchema
fieldOf _
= ((Word64 -> f Word64) -> CommandGetSchema -> f CommandGetSchema)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetSchema
-> f CommandGetSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchema -> Word64)
-> (CommandGetSchema -> Word64 -> CommandGetSchema)
-> Lens CommandGetSchema CommandGetSchema Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchema -> Word64
_CommandGetSchema'requestId
(\ x__ :: CommandGetSchema
x__ y__ :: Word64
y__ -> CommandGetSchema
x__ {_CommandGetSchema'requestId :: Word64
_CommandGetSchema'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchema "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text) -> CommandGetSchema -> f CommandGetSchema
fieldOf _
= ((Text -> f Text) -> CommandGetSchema -> f CommandGetSchema)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandGetSchema
-> f CommandGetSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchema -> Text)
-> (CommandGetSchema -> Text -> CommandGetSchema)
-> Lens CommandGetSchema CommandGetSchema Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchema -> Text
_CommandGetSchema'topic
(\ x__ :: CommandGetSchema
x__ y__ :: Text
y__ -> CommandGetSchema
x__ {_CommandGetSchema'topic :: Text
_CommandGetSchema'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchema "schemaVersion" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaVersion"
-> (ByteString -> f ByteString)
-> CommandGetSchema
-> f CommandGetSchema
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchema -> f CommandGetSchema)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> CommandGetSchema
-> f CommandGetSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchema -> Maybe ByteString)
-> (CommandGetSchema -> Maybe ByteString -> CommandGetSchema)
-> Lens
CommandGetSchema
CommandGetSchema
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchema -> Maybe ByteString
_CommandGetSchema'schemaVersion
(\ x__ :: CommandGetSchema
x__ y__ :: Maybe ByteString
y__ -> CommandGetSchema
x__ {_CommandGetSchema'schemaVersion :: Maybe ByteString
_CommandGetSchema'schemaVersion = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetSchema "maybe'schemaVersion" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'schemaVersion"
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchema
-> f CommandGetSchema
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchema -> f CommandGetSchema)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchema
-> f CommandGetSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchema -> Maybe ByteString)
-> (CommandGetSchema -> Maybe ByteString -> CommandGetSchema)
-> Lens
CommandGetSchema
CommandGetSchema
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchema -> Maybe ByteString
_CommandGetSchema'schemaVersion
(\ x__ :: CommandGetSchema
x__ y__ :: Maybe ByteString
y__ -> CommandGetSchema
x__ {_CommandGetSchema'schemaVersion :: Maybe ByteString
_CommandGetSchema'schemaVersion = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetSchema where
messageName :: Proxy CommandGetSchema -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandGetSchema"
packedMessageDescriptor :: Proxy CommandGetSchema -> ByteString
packedMessageDescriptor _
= "\n\
\\DLECommandGetSchema\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\DC4\n\
\\ENQtopic\CAN\STX \STX(\tR\ENQtopic\DC2%\n\
\\SOschema_version\CAN\ETX \SOH(\fR\rschemaVersion"
packedFileDescriptor :: Proxy CommandGetSchema -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetSchema)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetSchema
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetSchema Word64
-> FieldDescriptor CommandGetSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandGetSchema CommandGetSchema Word64 Word64
-> FieldAccessor CommandGetSchema Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchema
topic__field_descriptor :: FieldDescriptor CommandGetSchema
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetSchema Text
-> FieldDescriptor CommandGetSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandGetSchema CommandGetSchema Text Text
-> FieldAccessor CommandGetSchema Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchema
schemaVersion__field_descriptor :: FieldDescriptor CommandGetSchema
schemaVersion__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor CommandGetSchema ByteString
-> FieldDescriptor CommandGetSchema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_version"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
CommandGetSchema
CommandGetSchema
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor CommandGetSchema ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchema
in
[(Tag, FieldDescriptor CommandGetSchema)]
-> Map Tag (FieldDescriptor CommandGetSchema)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetSchema
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetSchema
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandGetSchema
schemaVersion__field_descriptor)]
unknownFields :: LensLike' f CommandGetSchema FieldSet
unknownFields
= (CommandGetSchema -> FieldSet)
-> (CommandGetSchema -> FieldSet -> CommandGetSchema)
-> Lens' CommandGetSchema FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchema -> FieldSet
_CommandGetSchema'_unknownFields
(\ x__ :: CommandGetSchema
x__ y__ :: FieldSet
y__ -> CommandGetSchema
x__ {_CommandGetSchema'_unknownFields :: FieldSet
_CommandGetSchema'_unknownFields = FieldSet
y__})
defMessage :: CommandGetSchema
defMessage
= $WCommandGetSchema'_constructor :: Word64 -> Text -> Maybe ByteString -> FieldSet -> CommandGetSchema
CommandGetSchema'_constructor
{_CommandGetSchema'requestId :: Word64
_CommandGetSchema'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetSchema'topic :: Text
_CommandGetSchema'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetSchema'schemaVersion :: Maybe ByteString
_CommandGetSchema'schemaVersion = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_CommandGetSchema'_unknownFields :: FieldSet
_CommandGetSchema'_unknownFields = []}
parseMessage :: Parser CommandGetSchema
parseMessage
= let
loop ::
CommandGetSchema
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetSchema
loop :: CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop x :: CommandGetSchema
x required'requestId :: Bool
required'requestId required'topic :: Bool
required'topic
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetSchema -> Parser CommandGetSchema
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandGetSchema CommandGetSchema FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandGetSchema -> CommandGetSchema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandGetSchema CommandGetSchema FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetSchema
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop
(Setter CommandGetSchema CommandGetSchema Word64 Word64
-> Word64 -> CommandGetSchema -> CommandGetSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetSchema
x)
Bool
Prelude.False
Bool
required'topic
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop
(Setter CommandGetSchema CommandGetSchema Text Text
-> Text -> CommandGetSchema -> CommandGetSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandGetSchema
x)
Bool
required'requestId
Bool
Prelude.False
26
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_version"
CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop
(Setter CommandGetSchema CommandGetSchema ByteString ByteString
-> ByteString -> CommandGetSchema -> CommandGetSchema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaVersion") ByteString
y CommandGetSchema
x)
Bool
required'requestId
Bool
required'topic
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop
(Setter CommandGetSchema CommandGetSchema FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandGetSchema -> CommandGetSchema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandGetSchema CommandGetSchema FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetSchema
x)
Bool
required'requestId
Bool
required'topic
in
Parser CommandGetSchema -> String -> Parser CommandGetSchema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetSchema -> Bool -> Bool -> Parser CommandGetSchema
loop CommandGetSchema
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandGetSchema"
buildMessage :: CommandGetSchema -> Builder
buildMessage
= \ _x :: CommandGetSchema
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandGetSchema CommandGetSchema Word64 Word64
-> CommandGetSchema -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetSchema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandGetSchema CommandGetSchema Text Text
-> CommandGetSchema -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandGetSchema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
CommandGetSchema
CommandGetSchema
(Maybe ByteString)
(Maybe ByteString)
-> CommandGetSchema -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion") CommandGetSchema
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandGetSchema CommandGetSchema FieldSet FieldSet
-> CommandGetSchema -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandGetSchema CommandGetSchema FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetSchema
_x))))
instance Control.DeepSeq.NFData CommandGetSchema where
rnf :: CommandGetSchema -> ()
rnf
= \ x__ :: CommandGetSchema
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchema -> FieldSet
_CommandGetSchema'_unknownFields CommandGetSchema
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchema -> Word64
_CommandGetSchema'requestId CommandGetSchema
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchema -> Text
_CommandGetSchema'topic CommandGetSchema
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchema -> Maybe ByteString
_CommandGetSchema'schemaVersion CommandGetSchema
x__) ())))
data CommandGetSchemaResponse
= CommandGetSchemaResponse'_constructor {CommandGetSchemaResponse -> Word64
_CommandGetSchemaResponse'requestId :: !Data.Word.Word64,
CommandGetSchemaResponse -> Maybe ServerError
_CommandGetSchemaResponse'errorCode :: !(Prelude.Maybe ServerError),
CommandGetSchemaResponse -> Maybe Text
_CommandGetSchemaResponse'errorMessage :: !(Prelude.Maybe Data.Text.Text),
CommandGetSchemaResponse -> Maybe Schema
_CommandGetSchemaResponse'schema :: !(Prelude.Maybe Schema),
CommandGetSchemaResponse -> Maybe ByteString
_CommandGetSchemaResponse'schemaVersion :: !(Prelude.Maybe Data.ByteString.ByteString),
CommandGetSchemaResponse -> FieldSet
_CommandGetSchemaResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
(CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> Eq CommandGetSchemaResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c/= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
== :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c== :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
Prelude.Eq, Eq CommandGetSchemaResponse
Eq CommandGetSchemaResponse =>
(CommandGetSchemaResponse -> CommandGetSchemaResponse -> Ordering)
-> (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> (CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool)
-> (CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse)
-> (CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse)
-> Ord CommandGetSchemaResponse
CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
CommandGetSchemaResponse -> CommandGetSchemaResponse -> Ordering
CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse
$cmin :: CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse
max :: CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse
$cmax :: CommandGetSchemaResponse
-> CommandGetSchemaResponse -> CommandGetSchemaResponse
>= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c>= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
> :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c> :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
<= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c<= :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
< :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
$c< :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Bool
compare :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Ordering
$ccompare :: CommandGetSchemaResponse -> CommandGetSchemaResponse -> Ordering
$cp1Ord :: Eq CommandGetSchemaResponse
Prelude.Ord)
instance Prelude.Show CommandGetSchemaResponse where
showsPrec :: Int -> CommandGetSchemaResponse -> ShowS
showsPrec _ __x :: CommandGetSchemaResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetSchemaResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetSchemaResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Word64)
-> (CommandGetSchemaResponse -> Word64 -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse CommandGetSchemaResponse Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Word64
_CommandGetSchemaResponse'requestId
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Word64
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'requestId :: Word64
_CommandGetSchemaResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "errorCode" ServerError where
fieldOf :: Proxy# "errorCode"
-> (ServerError -> f ServerError)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe ServerError)
-> (CommandGetSchemaResponse
-> Maybe ServerError -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe ServerError
_CommandGetSchemaResponse'errorCode
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe ServerError
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'errorCode :: Maybe ServerError
_CommandGetSchemaResponse'errorCode = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "maybe'errorCode" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'errorCode"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe ServerError)
-> (CommandGetSchemaResponse
-> Maybe ServerError -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe ServerError
_CommandGetSchemaResponse'errorCode
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe ServerError
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'errorCode :: Maybe ServerError
_CommandGetSchemaResponse'errorCode = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "errorMessage" Data.Text.Text where
fieldOf :: Proxy# "errorMessage"
-> (Text -> f Text)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe Text)
-> (CommandGetSchemaResponse
-> Maybe Text -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe Text
_CommandGetSchemaResponse'errorMessage
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe Text
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'errorMessage :: Maybe Text
_CommandGetSchemaResponse'errorMessage = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "maybe'errorMessage" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'errorMessage"
-> (Maybe Text -> f (Maybe Text))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe Text)
-> (CommandGetSchemaResponse
-> Maybe Text -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe Text
_CommandGetSchemaResponse'errorMessage
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe Text
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'errorMessage :: Maybe Text
_CommandGetSchemaResponse'errorMessage = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "schema" Schema where
fieldOf :: Proxy# "schema"
-> (Schema -> f Schema)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Schema -> f Schema) -> Maybe Schema -> f (Maybe Schema))
-> (Schema -> f Schema)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe Schema)
-> (CommandGetSchemaResponse
-> Maybe Schema -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Schema)
(Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe Schema
_CommandGetSchemaResponse'schema
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe Schema
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'schema :: Maybe Schema
_CommandGetSchemaResponse'schema = Maybe Schema
y__}))
(Schema -> Lens' (Maybe Schema) Schema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "maybe'schema" (Prelude.Maybe Schema) where
fieldOf :: Proxy# "maybe'schema"
-> (Maybe Schema -> f (Maybe Schema))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema))
-> (Maybe Schema -> f (Maybe Schema))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe Schema)
-> (CommandGetSchemaResponse
-> Maybe Schema -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Schema)
(Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe Schema
_CommandGetSchemaResponse'schema
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe Schema
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'schema :: Maybe Schema
_CommandGetSchemaResponse'schema = Maybe Schema
y__}))
(Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "schemaVersion" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaVersion"
-> (ByteString -> f ByteString)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe ByteString)
-> (CommandGetSchemaResponse
-> Maybe ByteString -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe ByteString
_CommandGetSchemaResponse'schemaVersion
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe ByteString
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetSchemaResponse'schemaVersion = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandGetSchemaResponse "maybe'schemaVersion" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'schemaVersion"
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchemaResponse -> f CommandGetSchemaResponse)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandGetSchemaResponse
-> f CommandGetSchemaResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetSchemaResponse -> Maybe ByteString)
-> (CommandGetSchemaResponse
-> Maybe ByteString -> CommandGetSchemaResponse)
-> Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> Maybe ByteString
_CommandGetSchemaResponse'schemaVersion
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: Maybe ByteString
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetSchemaResponse'schemaVersion = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetSchemaResponse where
messageName :: Proxy CommandGetSchemaResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetSchemaResponse"
packedMessageDescriptor :: Proxy CommandGetSchemaResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\CANCommandGetSchemaResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2,\n\
\\ACKschema\CAN\EOT \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2%\n\
\\SOschema_version\CAN\ENQ \SOH(\fR\rschemaVersion"
packedFileDescriptor :: Proxy CommandGetSchemaResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetSchemaResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetSchemaResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetSchemaResponse Word64
-> FieldDescriptor CommandGetSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetSchemaResponse CommandGetSchemaResponse Word64 Word64
-> FieldAccessor CommandGetSchemaResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchemaResponse
errorCode__field_descriptor :: FieldDescriptor CommandGetSchemaResponse
errorCode__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandGetSchemaResponse ServerError
-> FieldDescriptor CommandGetSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_code"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandGetSchemaResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchemaResponse
errorMessage__field_descriptor :: FieldDescriptor CommandGetSchemaResponse
errorMessage__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetSchemaResponse Text
-> FieldDescriptor CommandGetSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error_message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandGetSchemaResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchemaResponse
schema__field_descriptor :: FieldDescriptor CommandGetSchemaResponse
schema__field_descriptor
= String
-> FieldTypeDescriptor Schema
-> FieldAccessor CommandGetSchemaResponse Schema
-> FieldDescriptor CommandGetSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema"
(MessageOrGroup -> FieldTypeDescriptor Schema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Schema)
(Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Schema)
(Maybe Schema)
-> FieldAccessor CommandGetSchemaResponse Schema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchemaResponse
schemaVersion__field_descriptor :: FieldDescriptor CommandGetSchemaResponse
schemaVersion__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor CommandGetSchemaResponse ByteString
-> FieldDescriptor CommandGetSchemaResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_version"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor CommandGetSchemaResponse ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion")) ::
Data.ProtoLens.FieldDescriptor CommandGetSchemaResponse
in
[(Tag, FieldDescriptor CommandGetSchemaResponse)]
-> Map Tag (FieldDescriptor CommandGetSchemaResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetSchemaResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetSchemaResponse
errorCode__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandGetSchemaResponse
errorMessage__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandGetSchemaResponse
schema__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandGetSchemaResponse
schemaVersion__field_descriptor)]
unknownFields :: LensLike' f CommandGetSchemaResponse FieldSet
unknownFields
= (CommandGetSchemaResponse -> FieldSet)
-> (CommandGetSchemaResponse
-> FieldSet -> CommandGetSchemaResponse)
-> Lens' CommandGetSchemaResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetSchemaResponse -> FieldSet
_CommandGetSchemaResponse'_unknownFields
(\ x__ :: CommandGetSchemaResponse
x__ y__ :: FieldSet
y__ -> CommandGetSchemaResponse
x__ {_CommandGetSchemaResponse'_unknownFields :: FieldSet
_CommandGetSchemaResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandGetSchemaResponse
defMessage
= $WCommandGetSchemaResponse'_constructor :: Word64
-> Maybe ServerError
-> Maybe Text
-> Maybe Schema
-> Maybe ByteString
-> FieldSet
-> CommandGetSchemaResponse
CommandGetSchemaResponse'_constructor
{_CommandGetSchemaResponse'requestId :: Word64
_CommandGetSchemaResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetSchemaResponse'errorCode :: Maybe ServerError
_CommandGetSchemaResponse'errorCode = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandGetSchemaResponse'errorMessage :: Maybe Text
_CommandGetSchemaResponse'errorMessage = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandGetSchemaResponse'schema :: Maybe Schema
_CommandGetSchemaResponse'schema = Maybe Schema
forall a. Maybe a
Prelude.Nothing,
_CommandGetSchemaResponse'schemaVersion :: Maybe ByteString
_CommandGetSchemaResponse'schemaVersion = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_CommandGetSchemaResponse'_unknownFields :: FieldSet
_CommandGetSchemaResponse'_unknownFields = []}
parseMessage :: Parser CommandGetSchemaResponse
parseMessage
= let
loop ::
CommandGetSchemaResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetSchemaResponse
loop :: CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop x :: CommandGetSchemaResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetSchemaResponse -> Parser CommandGetSchemaResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetSchemaResponse CommandGetSchemaResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetSchemaResponse
-> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetSchemaResponse CommandGetSchemaResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetSchemaResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter
CommandGetSchemaResponse CommandGetSchemaResponse Word64 Word64
-> Word64 -> CommandGetSchemaResponse -> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetSchemaResponse
x)
Bool
Prelude.False
16
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error_code"
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter
CommandGetSchemaResponse
CommandGetSchemaResponse
ServerError
ServerError
-> ServerError
-> CommandGetSchemaResponse
-> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorCode") ServerError
y CommandGetSchemaResponse
x)
Bool
required'requestId
26
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"error_message"
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter CommandGetSchemaResponse CommandGetSchemaResponse Text Text
-> Text -> CommandGetSchemaResponse -> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"errorMessage") Text
y CommandGetSchemaResponse
x)
Bool
required'requestId
34
-> do Schema
y <- Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Schema -> Parser Schema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Schema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"schema"
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter
CommandGetSchemaResponse CommandGetSchemaResponse Schema Schema
-> Schema -> CommandGetSchemaResponse -> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") Schema
y CommandGetSchemaResponse
x)
Bool
required'requestId
42
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_version"
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter
CommandGetSchemaResponse
CommandGetSchemaResponse
ByteString
ByteString
-> ByteString
-> CommandGetSchemaResponse
-> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaVersion") ByteString
y CommandGetSchemaResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop
(Setter
CommandGetSchemaResponse CommandGetSchemaResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetSchemaResponse
-> CommandGetSchemaResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetSchemaResponse CommandGetSchemaResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetSchemaResponse
x)
Bool
required'requestId
in
Parser CommandGetSchemaResponse
-> String -> Parser CommandGetSchemaResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetSchemaResponse -> Bool -> Parser CommandGetSchemaResponse
loop CommandGetSchemaResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandGetSchemaResponse"
buildMessage :: CommandGetSchemaResponse -> Builder
buildMessage
= \ _x :: CommandGetSchemaResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetSchemaResponse
CommandGetSchemaResponse
Word64
Word64
-> CommandGetSchemaResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetSchemaResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandGetSchemaResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorCode") CommandGetSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Text)
(Maybe Text)
-> CommandGetSchemaResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'errorMessage" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'errorMessage") CommandGetSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Schema)
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe Schema)
(Maybe Schema)
-> CommandGetSchemaResponse -> Maybe Schema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema") CommandGetSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Schema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder)
-> (Schema -> ByteString) -> Schema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Schema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Schema
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
CommandGetSchemaResponse
CommandGetSchemaResponse
(Maybe ByteString)
(Maybe ByteString)
-> CommandGetSchemaResponse -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion") CommandGetSchemaResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetSchemaResponse
CommandGetSchemaResponse
FieldSet
FieldSet
-> CommandGetSchemaResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetSchemaResponse
CommandGetSchemaResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetSchemaResponse
_x))))))
instance Control.DeepSeq.NFData CommandGetSchemaResponse where
rnf :: CommandGetSchemaResponse -> ()
rnf
= \ x__ :: CommandGetSchemaResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> FieldSet
_CommandGetSchemaResponse'_unknownFields CommandGetSchemaResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> Word64
_CommandGetSchemaResponse'requestId CommandGetSchemaResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> Maybe ServerError
_CommandGetSchemaResponse'errorCode CommandGetSchemaResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> Maybe Text
_CommandGetSchemaResponse'errorMessage CommandGetSchemaResponse
x__)
(Maybe Schema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> Maybe Schema
_CommandGetSchemaResponse'schema CommandGetSchemaResponse
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetSchemaResponse -> Maybe ByteString
_CommandGetSchemaResponse'schemaVersion CommandGetSchemaResponse
x__) ())))))
data CommandGetTopicsOfNamespace
= CommandGetTopicsOfNamespace'_constructor {CommandGetTopicsOfNamespace -> Word64
_CommandGetTopicsOfNamespace'requestId :: !Data.Word.Word64,
CommandGetTopicsOfNamespace -> Text
_CommandGetTopicsOfNamespace'namespace :: !Data.Text.Text,
CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode :: !(Prelude.Maybe CommandGetTopicsOfNamespace'Mode),
CommandGetTopicsOfNamespace -> FieldSet
_CommandGetTopicsOfNamespace'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
(CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> Eq CommandGetTopicsOfNamespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c/= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
== :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c== :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
Prelude.Eq, Eq CommandGetTopicsOfNamespace
Eq CommandGetTopicsOfNamespace =>
(CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Ordering)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Bool)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace)
-> (CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace)
-> Ord CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Ordering
CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace
$cmin :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace
max :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace
$cmax :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace
>= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c>= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
> :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c> :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
<= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c<= :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
< :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
$c< :: CommandGetTopicsOfNamespace -> CommandGetTopicsOfNamespace -> Bool
compare :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Ordering
$ccompare :: CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace -> Ordering
$cp1Ord :: Eq CommandGetTopicsOfNamespace
Prelude.Ord)
instance Prelude.Show CommandGetTopicsOfNamespace where
showsPrec :: Int -> CommandGetTopicsOfNamespace -> ShowS
showsPrec _ __x :: CommandGetTopicsOfNamespace
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetTopicsOfNamespace -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetTopicsOfNamespace
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespace "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespace -> Word64)
-> (CommandGetTopicsOfNamespace
-> Word64 -> CommandGetTopicsOfNamespace)
-> Lens
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespace -> Word64
_CommandGetTopicsOfNamespace'requestId
(\ x__ :: CommandGetTopicsOfNamespace
x__ y__ :: Word64
y__ -> CommandGetTopicsOfNamespace
x__ {_CommandGetTopicsOfNamespace'requestId :: Word64
_CommandGetTopicsOfNamespace'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespace "namespace" Data.Text.Text where
fieldOf :: Proxy# "namespace"
-> (Text -> f Text)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
fieldOf _
= ((Text -> f Text)
-> CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespace -> Text)
-> (CommandGetTopicsOfNamespace
-> Text -> CommandGetTopicsOfNamespace)
-> Lens
CommandGetTopicsOfNamespace CommandGetTopicsOfNamespace Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespace -> Text
_CommandGetTopicsOfNamespace'namespace
(\ x__ :: CommandGetTopicsOfNamespace
x__ y__ :: Text
y__ -> CommandGetTopicsOfNamespace
x__ {_CommandGetTopicsOfNamespace'namespace :: Text
_CommandGetTopicsOfNamespace'namespace = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespace "mode" CommandGetTopicsOfNamespace'Mode where
fieldOf :: Proxy# "mode"
-> (CommandGetTopicsOfNamespace'Mode
-> f CommandGetTopicsOfNamespace'Mode)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
fieldOf _
= ((Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> ((CommandGetTopicsOfNamespace'Mode
-> f CommandGetTopicsOfNamespace'Mode)
-> Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> (CommandGetTopicsOfNamespace'Mode
-> f CommandGetTopicsOfNamespace'Mode)
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode)
-> (CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace)
-> Lens
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
(Maybe CommandGetTopicsOfNamespace'Mode)
(Maybe CommandGetTopicsOfNamespace'Mode)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode
(\ x__ :: CommandGetTopicsOfNamespace
x__ y__ :: Maybe CommandGetTopicsOfNamespace'Mode
y__ -> CommandGetTopicsOfNamespace
x__ {_CommandGetTopicsOfNamespace'mode :: Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode = Maybe CommandGetTopicsOfNamespace'Mode
y__}))
(CommandGetTopicsOfNamespace'Mode
-> Lens'
(Maybe CommandGetTopicsOfNamespace'Mode)
CommandGetTopicsOfNamespace'Mode
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT)
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespace "maybe'mode" (Prelude.Maybe CommandGetTopicsOfNamespace'Mode) where
fieldOf :: Proxy# "maybe'mode"
-> (Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
fieldOf _
= ((Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> CommandGetTopicsOfNamespace -> f CommandGetTopicsOfNamespace)
-> ((Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> (Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> CommandGetTopicsOfNamespace
-> f CommandGetTopicsOfNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode)
-> (CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace)
-> Lens
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
(Maybe CommandGetTopicsOfNamespace'Mode)
(Maybe CommandGetTopicsOfNamespace'Mode)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode
(\ x__ :: CommandGetTopicsOfNamespace
x__ y__ :: Maybe CommandGetTopicsOfNamespace'Mode
y__ -> CommandGetTopicsOfNamespace
x__ {_CommandGetTopicsOfNamespace'mode :: Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode = Maybe CommandGetTopicsOfNamespace'Mode
y__}))
(Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode))
-> Maybe CommandGetTopicsOfNamespace'Mode
-> f (Maybe CommandGetTopicsOfNamespace'Mode)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetTopicsOfNamespace where
messageName :: Proxy CommandGetTopicsOfNamespace -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetTopicsOfNamespace"
packedMessageDescriptor :: Proxy CommandGetTopicsOfNamespace -> ByteString
packedMessageDescriptor _
= "\n\
\\ESCCommandGetTopicsOfNamespace\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\FS\n\
\\tnamespace\CAN\STX \STX(\tR\tnamespace\DC2N\n\
\\EOTmode\CAN\ETX \SOH(\SO2..pulsar.proto.CommandGetTopicsOfNamespace.Mode:\n\
\PERSISTENTR\EOTmode\"3\n\
\\EOTMode\DC2\SO\n\
\\n\
\PERSISTENT\DLE\NUL\DC2\DC2\n\
\\SONON_PERSISTENT\DLE\SOH\DC2\a\n\
\\ETXALL\DLE\STX"
packedFileDescriptor :: Proxy CommandGetTopicsOfNamespace -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetTopicsOfNamespace)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetTopicsOfNamespace
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetTopicsOfNamespace Word64
-> FieldDescriptor CommandGetTopicsOfNamespace
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
Word64
Word64
-> FieldAccessor CommandGetTopicsOfNamespace Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetTopicsOfNamespace
namespace__field_descriptor :: FieldDescriptor CommandGetTopicsOfNamespace
namespace__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetTopicsOfNamespace Text
-> FieldDescriptor CommandGetTopicsOfNamespace
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"namespace"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens
CommandGetTopicsOfNamespace CommandGetTopicsOfNamespace Text Text
-> FieldAccessor CommandGetTopicsOfNamespace Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "namespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"namespace")) ::
Data.ProtoLens.FieldDescriptor CommandGetTopicsOfNamespace
mode__field_descriptor :: FieldDescriptor CommandGetTopicsOfNamespace
mode__field_descriptor
= String
-> FieldTypeDescriptor CommandGetTopicsOfNamespace'Mode
-> FieldAccessor
CommandGetTopicsOfNamespace CommandGetTopicsOfNamespace'Mode
-> FieldDescriptor CommandGetTopicsOfNamespace
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"mode"
(ScalarField CommandGetTopicsOfNamespace'Mode
-> FieldTypeDescriptor CommandGetTopicsOfNamespace'Mode
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandGetTopicsOfNamespace'Mode
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandGetTopicsOfNamespace'Mode)
(Lens
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
(Maybe CommandGetTopicsOfNamespace'Mode)
(Maybe CommandGetTopicsOfNamespace'Mode)
-> FieldAccessor
CommandGetTopicsOfNamespace CommandGetTopicsOfNamespace'Mode
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'mode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'mode")) ::
Data.ProtoLens.FieldDescriptor CommandGetTopicsOfNamespace
in
[(Tag, FieldDescriptor CommandGetTopicsOfNamespace)]
-> Map Tag (FieldDescriptor CommandGetTopicsOfNamespace)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetTopicsOfNamespace
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetTopicsOfNamespace
namespace__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandGetTopicsOfNamespace
mode__field_descriptor)]
unknownFields :: LensLike' f CommandGetTopicsOfNamespace FieldSet
unknownFields
= (CommandGetTopicsOfNamespace -> FieldSet)
-> (CommandGetTopicsOfNamespace
-> FieldSet -> CommandGetTopicsOfNamespace)
-> Lens' CommandGetTopicsOfNamespace FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespace -> FieldSet
_CommandGetTopicsOfNamespace'_unknownFields
(\ x__ :: CommandGetTopicsOfNamespace
x__ y__ :: FieldSet
y__
-> CommandGetTopicsOfNamespace
x__ {_CommandGetTopicsOfNamespace'_unknownFields :: FieldSet
_CommandGetTopicsOfNamespace'_unknownFields = FieldSet
y__})
defMessage :: CommandGetTopicsOfNamespace
defMessage
= $WCommandGetTopicsOfNamespace'_constructor :: Word64
-> Text
-> Maybe CommandGetTopicsOfNamespace'Mode
-> FieldSet
-> CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace'_constructor
{_CommandGetTopicsOfNamespace'requestId :: Word64
_CommandGetTopicsOfNamespace'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetTopicsOfNamespace'namespace :: Text
_CommandGetTopicsOfNamespace'namespace = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetTopicsOfNamespace'mode :: Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode = Maybe CommandGetTopicsOfNamespace'Mode
forall a. Maybe a
Prelude.Nothing,
_CommandGetTopicsOfNamespace'_unknownFields :: FieldSet
_CommandGetTopicsOfNamespace'_unknownFields = []}
parseMessage :: Parser CommandGetTopicsOfNamespace
parseMessage
= let
loop ::
CommandGetTopicsOfNamespace
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetTopicsOfNamespace
loop :: CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop x :: CommandGetTopicsOfNamespace
x required'namespace :: Bool
required'namespace required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'namespace then (:) "namespace" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetTopicsOfNamespace -> Parser CommandGetTopicsOfNamespace
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandGetTopicsOfNamespace
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop
(Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
Word64
Word64
-> Word64
-> CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetTopicsOfNamespace
x)
Bool
required'namespace
Bool
Prelude.False
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"namespace"
CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop
(Setter
CommandGetTopicsOfNamespace CommandGetTopicsOfNamespace Text Text
-> Text
-> CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "namespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"namespace") Text
y CommandGetTopicsOfNamespace
x)
Bool
Prelude.False
Bool
required'requestId
24
-> do CommandGetTopicsOfNamespace'Mode
y <- Parser CommandGetTopicsOfNamespace'Mode
-> String -> Parser CommandGetTopicsOfNamespace'Mode
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandGetTopicsOfNamespace'Mode)
-> Parser Int -> Parser CommandGetTopicsOfNamespace'Mode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandGetTopicsOfNamespace'Mode
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"mode"
CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop
(Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "mode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"mode") CommandGetTopicsOfNamespace'Mode
y CommandGetTopicsOfNamespace
x)
Bool
required'namespace
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop
(Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetTopicsOfNamespace
-> CommandGetTopicsOfNamespace
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetTopicsOfNamespace
x)
Bool
required'namespace
Bool
required'requestId
in
Parser CommandGetTopicsOfNamespace
-> String -> Parser CommandGetTopicsOfNamespace
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandGetTopicsOfNamespace
-> Bool -> Bool -> Parser CommandGetTopicsOfNamespace
loop CommandGetTopicsOfNamespace
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandGetTopicsOfNamespace"
buildMessage :: CommandGetTopicsOfNamespace -> Builder
buildMessage
= \ _x :: CommandGetTopicsOfNamespace
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
Word64
Word64
-> CommandGetTopicsOfNamespace -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetTopicsOfNamespace
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike
Text
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
Text
Text
-> CommandGetTopicsOfNamespace -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "namespace" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"namespace") CommandGetTopicsOfNamespace
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandGetTopicsOfNamespace'Mode)
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
(Maybe CommandGetTopicsOfNamespace'Mode)
(Maybe CommandGetTopicsOfNamespace'Mode)
-> CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'mode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'mode") CommandGetTopicsOfNamespace
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandGetTopicsOfNamespace'Mode
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Int -> Builder)
-> (CommandGetTopicsOfNamespace'Mode -> Int)
-> CommandGetTopicsOfNamespace'Mode
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandGetTopicsOfNamespace'Mode -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CommandGetTopicsOfNamespace'Mode
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
-> CommandGetTopicsOfNamespace -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetTopicsOfNamespace
CommandGetTopicsOfNamespace
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetTopicsOfNamespace
_x))))
instance Control.DeepSeq.NFData CommandGetTopicsOfNamespace where
rnf :: CommandGetTopicsOfNamespace -> ()
rnf
= \ x__ :: CommandGetTopicsOfNamespace
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespace -> FieldSet
_CommandGetTopicsOfNamespace'_unknownFields CommandGetTopicsOfNamespace
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespace -> Word64
_CommandGetTopicsOfNamespace'requestId CommandGetTopicsOfNamespace
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespace -> Text
_CommandGetTopicsOfNamespace'namespace CommandGetTopicsOfNamespace
x__)
(Maybe CommandGetTopicsOfNamespace'Mode -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespace
-> Maybe CommandGetTopicsOfNamespace'Mode
_CommandGetTopicsOfNamespace'mode CommandGetTopicsOfNamespace
x__) ())))
data CommandGetTopicsOfNamespace'Mode
= CommandGetTopicsOfNamespace'PERSISTENT |
CommandGetTopicsOfNamespace'NON_PERSISTENT |
CommandGetTopicsOfNamespace'ALL
deriving stock (Int -> CommandGetTopicsOfNamespace'Mode -> ShowS
[CommandGetTopicsOfNamespace'Mode] -> ShowS
CommandGetTopicsOfNamespace'Mode -> String
(Int -> CommandGetTopicsOfNamespace'Mode -> ShowS)
-> (CommandGetTopicsOfNamespace'Mode -> String)
-> ([CommandGetTopicsOfNamespace'Mode] -> ShowS)
-> Show CommandGetTopicsOfNamespace'Mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandGetTopicsOfNamespace'Mode] -> ShowS
$cshowList :: [CommandGetTopicsOfNamespace'Mode] -> ShowS
show :: CommandGetTopicsOfNamespace'Mode -> String
$cshow :: CommandGetTopicsOfNamespace'Mode -> String
showsPrec :: Int -> CommandGetTopicsOfNamespace'Mode -> ShowS
$cshowsPrec :: Int -> CommandGetTopicsOfNamespace'Mode -> ShowS
Prelude.Show, CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
(CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> Eq CommandGetTopicsOfNamespace'Mode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c/= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
== :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c== :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
Prelude.Eq, Eq CommandGetTopicsOfNamespace'Mode
Eq CommandGetTopicsOfNamespace'Mode =>
(CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Ordering)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode)
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode)
-> Ord CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Ordering
CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
$cmin :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
max :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
$cmax :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
>= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c>= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
> :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c> :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
<= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c<= :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
< :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
$c< :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Bool
compare :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Ordering
$ccompare :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode -> Ordering
$cp1Ord :: Eq CommandGetTopicsOfNamespace'Mode
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandGetTopicsOfNamespace'Mode where
maybeToEnum :: Int -> Maybe CommandGetTopicsOfNamespace'Mode
maybeToEnum 0 = CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT
maybeToEnum 1
= CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'NON_PERSISTENT
maybeToEnum 2 = CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'ALL
maybeToEnum _ = Maybe CommandGetTopicsOfNamespace'Mode
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandGetTopicsOfNamespace'Mode -> String
showEnum CommandGetTopicsOfNamespace'PERSISTENT = "PERSISTENT"
showEnum CommandGetTopicsOfNamespace'NON_PERSISTENT
= "NON_PERSISTENT"
showEnum CommandGetTopicsOfNamespace'ALL = "ALL"
readEnum :: String -> Maybe CommandGetTopicsOfNamespace'Mode
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PERSISTENT"
= CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "NON_PERSISTENT"
= CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'NON_PERSISTENT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ALL"
= CommandGetTopicsOfNamespace'Mode
-> Maybe CommandGetTopicsOfNamespace'Mode
forall a. a -> Maybe a
Prelude.Just CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'ALL
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandGetTopicsOfNamespace'Mode)
-> Maybe CommandGetTopicsOfNamespace'Mode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandGetTopicsOfNamespace'Mode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandGetTopicsOfNamespace'Mode where
minBound :: CommandGetTopicsOfNamespace'Mode
minBound = CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT
maxBound :: CommandGetTopicsOfNamespace'Mode
maxBound = CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'ALL
instance Prelude.Enum CommandGetTopicsOfNamespace'Mode where
toEnum :: Int -> CommandGetTopicsOfNamespace'Mode
toEnum k__ :: Int
k__
= CommandGetTopicsOfNamespace'Mode
-> (CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode)
-> Maybe CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandGetTopicsOfNamespace'Mode
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum Mode: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
forall a. a -> a
Prelude.id
(Int -> Maybe CommandGetTopicsOfNamespace'Mode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandGetTopicsOfNamespace'Mode -> Int
fromEnum CommandGetTopicsOfNamespace'PERSISTENT = 0
fromEnum CommandGetTopicsOfNamespace'NON_PERSISTENT = 1
fromEnum CommandGetTopicsOfNamespace'ALL = 2
succ :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
succ CommandGetTopicsOfNamespace'ALL
= String -> CommandGetTopicsOfNamespace'Mode
forall a. HasCallStack => String -> a
Prelude.error
"CommandGetTopicsOfNamespace'Mode.succ: bad argument CommandGetTopicsOfNamespace'ALL. This value would be out of bounds."
succ CommandGetTopicsOfNamespace'PERSISTENT
= CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'NON_PERSISTENT
succ CommandGetTopicsOfNamespace'NON_PERSISTENT
= CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'ALL
pred :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
pred CommandGetTopicsOfNamespace'PERSISTENT
= String -> CommandGetTopicsOfNamespace'Mode
forall a. HasCallStack => String -> a
Prelude.error
"CommandGetTopicsOfNamespace'Mode.pred: bad argument CommandGetTopicsOfNamespace'PERSISTENT. This value would be out of bounds."
pred CommandGetTopicsOfNamespace'NON_PERSISTENT
= CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT
pred CommandGetTopicsOfNamespace'ALL
= CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'NON_PERSISTENT
enumFrom :: CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
enumFrom = CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
enumFromTo = CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
enumFromThen = CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
enumFromThenTo = CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> CommandGetTopicsOfNamespace'Mode
-> [CommandGetTopicsOfNamespace'Mode]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandGetTopicsOfNamespace'Mode where
fieldDefault :: CommandGetTopicsOfNamespace'Mode
fieldDefault = CommandGetTopicsOfNamespace'Mode
CommandGetTopicsOfNamespace'PERSISTENT
instance Control.DeepSeq.NFData CommandGetTopicsOfNamespace'Mode where
rnf :: CommandGetTopicsOfNamespace'Mode -> ()
rnf x__ :: CommandGetTopicsOfNamespace'Mode
x__ = CommandGetTopicsOfNamespace'Mode -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandGetTopicsOfNamespace'Mode
x__ ()
data CommandGetTopicsOfNamespaceResponse
= CommandGetTopicsOfNamespaceResponse'_constructor {CommandGetTopicsOfNamespaceResponse -> Word64
_CommandGetTopicsOfNamespaceResponse'requestId :: !Data.Word.Word64,
CommandGetTopicsOfNamespaceResponse -> Vector Text
_CommandGetTopicsOfNamespaceResponse'topics :: !(Data.Vector.Vector Data.Text.Text),
CommandGetTopicsOfNamespaceResponse -> FieldSet
_CommandGetTopicsOfNamespaceResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
(CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> Eq CommandGetTopicsOfNamespaceResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c/= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
== :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c== :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
Prelude.Eq, Eq CommandGetTopicsOfNamespaceResponse
Eq CommandGetTopicsOfNamespaceResponse =>
(CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Ordering)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse)
-> (CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse)
-> Ord CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Ordering
CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
$cmin :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
max :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
$cmax :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
>= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c>= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
> :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c> :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
<= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c<= :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
< :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
$c< :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Bool
compare :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Ordering
$ccompare :: CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse -> Ordering
$cp1Ord :: Eq CommandGetTopicsOfNamespaceResponse
Prelude.Ord)
instance Prelude.Show CommandGetTopicsOfNamespaceResponse where
showsPrec :: Int -> CommandGetTopicsOfNamespaceResponse -> ShowS
showsPrec _ __x :: CommandGetTopicsOfNamespaceResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandGetTopicsOfNamespaceResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandGetTopicsOfNamespaceResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespaceResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespaceResponse -> Word64)
-> (CommandGetTopicsOfNamespaceResponse
-> Word64 -> CommandGetTopicsOfNamespaceResponse)
-> Lens
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespaceResponse -> Word64
_CommandGetTopicsOfNamespaceResponse'requestId
(\ x__ :: CommandGetTopicsOfNamespaceResponse
x__ y__ :: Word64
y__
-> CommandGetTopicsOfNamespaceResponse
x__ {_CommandGetTopicsOfNamespaceResponse'requestId :: Word64
_CommandGetTopicsOfNamespaceResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespaceResponse "topics" [Data.Text.Text] where
fieldOf :: Proxy# "topics"
-> ([Text] -> f [Text])
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
fieldOf _
= ((Vector Text -> f (Vector Text))
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> (([Text] -> f [Text]) -> Vector Text -> f (Vector Text))
-> ([Text] -> f [Text])
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespaceResponse -> Vector Text)
-> (CommandGetTopicsOfNamespaceResponse
-> Vector Text -> CommandGetTopicsOfNamespaceResponse)
-> Lens
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
(Vector Text)
(Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespaceResponse -> Vector Text
_CommandGetTopicsOfNamespaceResponse'topics
(\ x__ :: CommandGetTopicsOfNamespaceResponse
x__ y__ :: Vector Text
y__
-> CommandGetTopicsOfNamespaceResponse
x__ {_CommandGetTopicsOfNamespaceResponse'topics :: Vector Text
_CommandGetTopicsOfNamespaceResponse'topics = Vector Text
y__}))
((Vector Text -> [Text])
-> (Vector Text -> [Text] -> Vector Text)
-> Lens (Vector Text) (Vector Text) [Text] [Text]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Text -> [Text]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Text]
y__ -> [Text] -> Vector Text
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Text]
y__))
instance Data.ProtoLens.Field.HasField CommandGetTopicsOfNamespaceResponse "vec'topics" (Data.Vector.Vector Data.Text.Text) where
fieldOf :: Proxy# "vec'topics"
-> (Vector Text -> f (Vector Text))
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
fieldOf _
= ((Vector Text -> f (Vector Text))
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse)
-> ((Vector Text -> f (Vector Text))
-> Vector Text -> f (Vector Text))
-> (Vector Text -> f (Vector Text))
-> CommandGetTopicsOfNamespaceResponse
-> f CommandGetTopicsOfNamespaceResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandGetTopicsOfNamespaceResponse -> Vector Text)
-> (CommandGetTopicsOfNamespaceResponse
-> Vector Text -> CommandGetTopicsOfNamespaceResponse)
-> Lens
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
(Vector Text)
(Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespaceResponse -> Vector Text
_CommandGetTopicsOfNamespaceResponse'topics
(\ x__ :: CommandGetTopicsOfNamespaceResponse
x__ y__ :: Vector Text
y__
-> CommandGetTopicsOfNamespaceResponse
x__ {_CommandGetTopicsOfNamespaceResponse'topics :: Vector Text
_CommandGetTopicsOfNamespaceResponse'topics = Vector Text
y__}))
(Vector Text -> f (Vector Text)) -> Vector Text -> f (Vector Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandGetTopicsOfNamespaceResponse where
messageName :: Proxy CommandGetTopicsOfNamespaceResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandGetTopicsOfNamespaceResponse"
packedMessageDescriptor :: Proxy CommandGetTopicsOfNamespaceResponse -> ByteString
packedMessageDescriptor _
= "\n\
\#CommandGetTopicsOfNamespaceResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\SYN\n\
\\ACKtopics\CAN\STX \ETX(\tR\ACKtopics"
packedFileDescriptor :: Proxy CommandGetTopicsOfNamespaceResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandGetTopicsOfNamespaceResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandGetTopicsOfNamespaceResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandGetTopicsOfNamespaceResponse Word64
-> FieldDescriptor CommandGetTopicsOfNamespaceResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
Word64
Word64
-> FieldAccessor CommandGetTopicsOfNamespaceResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandGetTopicsOfNamespaceResponse
topics__field_descriptor :: FieldDescriptor CommandGetTopicsOfNamespaceResponse
topics__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandGetTopicsOfNamespaceResponse Text
-> FieldDescriptor CommandGetTopicsOfNamespaceResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topics"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Packing
-> Lens' CommandGetTopicsOfNamespaceResponse [Text]
-> FieldAccessor CommandGetTopicsOfNamespaceResponse Text
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "topics" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topics")) ::
Data.ProtoLens.FieldDescriptor CommandGetTopicsOfNamespaceResponse
in
[(Tag, FieldDescriptor CommandGetTopicsOfNamespaceResponse)]
-> Map Tag (FieldDescriptor CommandGetTopicsOfNamespaceResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandGetTopicsOfNamespaceResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandGetTopicsOfNamespaceResponse
topics__field_descriptor)]
unknownFields :: LensLike' f CommandGetTopicsOfNamespaceResponse FieldSet
unknownFields
= (CommandGetTopicsOfNamespaceResponse -> FieldSet)
-> (CommandGetTopicsOfNamespaceResponse
-> FieldSet -> CommandGetTopicsOfNamespaceResponse)
-> Lens' CommandGetTopicsOfNamespaceResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandGetTopicsOfNamespaceResponse -> FieldSet
_CommandGetTopicsOfNamespaceResponse'_unknownFields
(\ x__ :: CommandGetTopicsOfNamespaceResponse
x__ y__ :: FieldSet
y__
-> CommandGetTopicsOfNamespaceResponse
x__ {_CommandGetTopicsOfNamespaceResponse'_unknownFields :: FieldSet
_CommandGetTopicsOfNamespaceResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandGetTopicsOfNamespaceResponse
defMessage
= $WCommandGetTopicsOfNamespaceResponse'_constructor :: Word64
-> Vector Text -> FieldSet -> CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse'_constructor
{_CommandGetTopicsOfNamespaceResponse'requestId :: Word64
_CommandGetTopicsOfNamespaceResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandGetTopicsOfNamespaceResponse'topics :: Vector Text
_CommandGetTopicsOfNamespaceResponse'topics = Vector Text
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandGetTopicsOfNamespaceResponse'_unknownFields :: FieldSet
_CommandGetTopicsOfNamespaceResponse'_unknownFields = []}
parseMessage :: Parser CommandGetTopicsOfNamespaceResponse
parseMessage
= let
loop ::
CommandGetTopicsOfNamespaceResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Data.Text.Text
-> Data.ProtoLens.Encoding.Bytes.Parser CommandGetTopicsOfNamespaceResponse
loop :: CommandGetTopicsOfNamespaceResponse
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandGetTopicsOfNamespaceResponse
loop x :: CommandGetTopicsOfNamespaceResponse
x required'requestId :: Bool
required'requestId mutable'topics :: Growing Vector RealWorld Text
mutable'topics
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector Text
frozen'topics <- IO (Vector Text) -> Parser (Vector Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text -> IO (Vector Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'topics)
(let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandGetTopicsOfNamespaceResponse
-> Parser CommandGetTopicsOfNamespaceResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
(Vector Text)
(Vector Text)
-> Vector Text
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'topics" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'topics") Vector Text
frozen'topics CommandGetTopicsOfNamespaceResponse
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandGetTopicsOfNamespaceResponse
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandGetTopicsOfNamespaceResponse
loop
(Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
Word64
Word64
-> Word64
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandGetTopicsOfNamespaceResponse
x)
Bool
Prelude.False
Growing Vector RealWorld Text
mutable'topics
18
-> do !Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topics"
Growing Vector RealWorld Text
v <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text
-> Text -> IO (Growing Vector (PrimState IO) Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'topics Text
y)
CommandGetTopicsOfNamespaceResponse
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandGetTopicsOfNamespaceResponse
loop CommandGetTopicsOfNamespaceResponse
x Bool
required'requestId Growing Vector RealWorld Text
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandGetTopicsOfNamespaceResponse
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandGetTopicsOfNamespaceResponse
loop
(Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandGetTopicsOfNamespaceResponse
-> CommandGetTopicsOfNamespaceResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandGetTopicsOfNamespaceResponse
x)
Bool
required'requestId
Growing Vector RealWorld Text
mutable'topics
in
Parser CommandGetTopicsOfNamespaceResponse
-> String -> Parser CommandGetTopicsOfNamespaceResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld Text
mutable'topics <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandGetTopicsOfNamespaceResponse
-> Bool
-> Growing Vector RealWorld Text
-> Parser CommandGetTopicsOfNamespaceResponse
loop CommandGetTopicsOfNamespaceResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld Text
mutable'topics)
"CommandGetTopicsOfNamespaceResponse"
buildMessage :: CommandGetTopicsOfNamespaceResponse -> Builder
buildMessage
= \ _x :: CommandGetTopicsOfNamespaceResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
Word64
Word64
-> CommandGetTopicsOfNamespaceResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandGetTopicsOfNamespaceResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Text -> Builder) -> Vector Text -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Text
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FoldLike
(Vector Text)
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
(Vector Text)
(Vector Text)
-> CommandGetTopicsOfNamespaceResponse -> Vector Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "vec'topics" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'topics") CommandGetTopicsOfNamespaceResponse
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
-> CommandGetTopicsOfNamespaceResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandGetTopicsOfNamespaceResponse
CommandGetTopicsOfNamespaceResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandGetTopicsOfNamespaceResponse
_x)))
instance Control.DeepSeq.NFData CommandGetTopicsOfNamespaceResponse where
rnf :: CommandGetTopicsOfNamespaceResponse -> ()
rnf
= \ x__ :: CommandGetTopicsOfNamespaceResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespaceResponse -> FieldSet
_CommandGetTopicsOfNamespaceResponse'_unknownFields CommandGetTopicsOfNamespaceResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespaceResponse -> Word64
_CommandGetTopicsOfNamespaceResponse'requestId CommandGetTopicsOfNamespaceResponse
x__)
(Vector Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandGetTopicsOfNamespaceResponse -> Vector Text
_CommandGetTopicsOfNamespaceResponse'topics CommandGetTopicsOfNamespaceResponse
x__) ()))
data CommandLookupTopic
= CommandLookupTopic'_constructor {CommandLookupTopic -> Text
_CommandLookupTopic'topic :: !Data.Text.Text,
CommandLookupTopic -> Word64
_CommandLookupTopic'requestId :: !Data.Word.Word64,
CommandLookupTopic -> Maybe Bool
_CommandLookupTopic'authoritative :: !(Prelude.Maybe Prelude.Bool),
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalPrincipal :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthData :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthMethod :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'advertisedListenerName :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopic -> FieldSet
_CommandLookupTopic'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandLookupTopic -> CommandLookupTopic -> Bool
(CommandLookupTopic -> CommandLookupTopic -> Bool)
-> (CommandLookupTopic -> CommandLookupTopic -> Bool)
-> Eq CommandLookupTopic
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c/= :: CommandLookupTopic -> CommandLookupTopic -> Bool
== :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c== :: CommandLookupTopic -> CommandLookupTopic -> Bool
Prelude.Eq, Eq CommandLookupTopic
Eq CommandLookupTopic =>
(CommandLookupTopic -> CommandLookupTopic -> Ordering)
-> (CommandLookupTopic -> CommandLookupTopic -> Bool)
-> (CommandLookupTopic -> CommandLookupTopic -> Bool)
-> (CommandLookupTopic -> CommandLookupTopic -> Bool)
-> (CommandLookupTopic -> CommandLookupTopic -> Bool)
-> (CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic)
-> (CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic)
-> Ord CommandLookupTopic
CommandLookupTopic -> CommandLookupTopic -> Bool
CommandLookupTopic -> CommandLookupTopic -> Ordering
CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic
$cmin :: CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic
max :: CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic
$cmax :: CommandLookupTopic -> CommandLookupTopic -> CommandLookupTopic
>= :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c>= :: CommandLookupTopic -> CommandLookupTopic -> Bool
> :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c> :: CommandLookupTopic -> CommandLookupTopic -> Bool
<= :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c<= :: CommandLookupTopic -> CommandLookupTopic -> Bool
< :: CommandLookupTopic -> CommandLookupTopic -> Bool
$c< :: CommandLookupTopic -> CommandLookupTopic -> Bool
compare :: CommandLookupTopic -> CommandLookupTopic -> Ordering
$ccompare :: CommandLookupTopic -> CommandLookupTopic -> Ordering
$cp1Ord :: Eq CommandLookupTopic
Prelude.Ord)
instance Prelude.Show CommandLookupTopic where
showsPrec :: Int -> CommandLookupTopic -> ShowS
showsPrec _ __x :: CommandLookupTopic
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandLookupTopic -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandLookupTopic
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandLookupTopic "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Text)
-> (CommandLookupTopic -> Text -> CommandLookupTopic)
-> Lens CommandLookupTopic CommandLookupTopic Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Text
_CommandLookupTopic'topic
(\ x__ :: CommandLookupTopic
x__ y__ :: Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'topic :: Text
_CommandLookupTopic'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Word64 -> f Word64)
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Word64)
-> (CommandLookupTopic -> Word64 -> CommandLookupTopic)
-> Lens CommandLookupTopic CommandLookupTopic Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Word64
_CommandLookupTopic'requestId
(\ x__ :: CommandLookupTopic
x__ y__ :: Word64
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'requestId :: Word64
_CommandLookupTopic'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "authoritative" Prelude.Bool where
fieldOf :: Proxy# "authoritative"
-> (Bool -> f Bool) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Bool)
-> (CommandLookupTopic -> Maybe Bool -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Bool
_CommandLookupTopic'authoritative
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Bool
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'authoritative :: Maybe Bool
_CommandLookupTopic'authoritative = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandLookupTopic "maybe'authoritative" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'authoritative"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Bool)
-> (CommandLookupTopic -> Maybe Bool -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Bool
_CommandLookupTopic'authoritative
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Bool
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'authoritative :: Maybe Bool
_CommandLookupTopic'authoritative = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "originalPrincipal" Data.Text.Text where
fieldOf :: Proxy# "originalPrincipal"
-> (Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalPrincipal
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalPrincipal :: Maybe Text
_CommandLookupTopic'originalPrincipal = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopic "maybe'originalPrincipal" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalPrincipal"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalPrincipal
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalPrincipal :: Maybe Text
_CommandLookupTopic'originalPrincipal = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "originalAuthData" Data.Text.Text where
fieldOf :: Proxy# "originalAuthData"
-> (Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthData
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalAuthData :: Maybe Text
_CommandLookupTopic'originalAuthData = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopic "maybe'originalAuthData" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthData"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthData
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalAuthData :: Maybe Text
_CommandLookupTopic'originalAuthData = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "originalAuthMethod" Data.Text.Text where
fieldOf :: Proxy# "originalAuthMethod"
-> (Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthMethod
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalAuthMethod :: Maybe Text
_CommandLookupTopic'originalAuthMethod = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopic "maybe'originalAuthMethod" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthMethod"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthMethod
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'originalAuthMethod :: Maybe Text
_CommandLookupTopic'originalAuthMethod = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopic "advertisedListenerName" Data.Text.Text where
fieldOf :: Proxy# "advertisedListenerName"
-> (Text -> f Text) -> CommandLookupTopic -> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'advertisedListenerName
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__
-> CommandLookupTopic
x__ {_CommandLookupTopic'advertisedListenerName :: Maybe Text
_CommandLookupTopic'advertisedListenerName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopic "maybe'advertisedListenerName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'advertisedListenerName"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopic -> f CommandLookupTopic)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopic
-> f CommandLookupTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopic -> Maybe Text)
-> (CommandLookupTopic -> Maybe Text -> CommandLookupTopic)
-> Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> Maybe Text
_CommandLookupTopic'advertisedListenerName
(\ x__ :: CommandLookupTopic
x__ y__ :: Maybe Text
y__
-> CommandLookupTopic
x__ {_CommandLookupTopic'advertisedListenerName :: Maybe Text
_CommandLookupTopic'advertisedListenerName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandLookupTopic where
messageName :: Proxy CommandLookupTopic -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandLookupTopic"
packedMessageDescriptor :: Proxy CommandLookupTopic -> ByteString
packedMessageDescriptor _
= "\n\
\\DC2CommandLookupTopic\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2+\n\
\\rauthoritative\CAN\ETX \SOH(\b:\ENQfalseR\rauthoritative\DC2-\n\
\\DC2original_principal\CAN\EOT \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\ENQ \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\ACK \SOH(\tR\DC2originalAuthMethod\DC28\n\
\\CANadvertised_listener_name\CAN\a \SOH(\tR\SYNadvertisedListenerName"
packedFileDescriptor :: Proxy CommandLookupTopic -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandLookupTopic)
fieldsByTag
= let
topic__field_descriptor :: FieldDescriptor CommandLookupTopic
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopic Text
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandLookupTopic CommandLookupTopic Text Text
-> FieldAccessor CommandLookupTopic Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
requestId__field_descriptor :: FieldDescriptor CommandLookupTopic
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandLookupTopic Word64
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandLookupTopic CommandLookupTopic Word64 Word64
-> FieldAccessor CommandLookupTopic Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
authoritative__field_descriptor :: FieldDescriptor CommandLookupTopic
authoritative__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandLookupTopic Bool
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"authoritative"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
CommandLookupTopic CommandLookupTopic (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandLookupTopic Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authoritative")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
originalPrincipal__field_descriptor :: FieldDescriptor CommandLookupTopic
originalPrincipal__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopic Text
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_principal"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
-> FieldAccessor CommandLookupTopic Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
originalAuthData__field_descriptor :: FieldDescriptor CommandLookupTopic
originalAuthData__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopic Text
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_data"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
-> FieldAccessor CommandLookupTopic Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
originalAuthMethod__field_descriptor :: FieldDescriptor CommandLookupTopic
originalAuthMethod__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopic Text
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_method"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
-> FieldAccessor CommandLookupTopic Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
advertisedListenerName__field_descriptor :: FieldDescriptor CommandLookupTopic
advertisedListenerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopic Text
-> FieldDescriptor CommandLookupTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"advertised_listener_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopic CommandLookupTopic (Maybe Text) (Maybe Text)
-> FieldAccessor CommandLookupTopic Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'advertisedListenerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'advertisedListenerName")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopic
in
[(Tag, FieldDescriptor CommandLookupTopic)]
-> Map Tag (FieldDescriptor CommandLookupTopic)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandLookupTopic
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandLookupTopic
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandLookupTopic
authoritative__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandLookupTopic
originalPrincipal__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandLookupTopic
originalAuthData__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandLookupTopic
originalAuthMethod__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandLookupTopic
advertisedListenerName__field_descriptor)]
unknownFields :: LensLike' f CommandLookupTopic FieldSet
unknownFields
= (CommandLookupTopic -> FieldSet)
-> (CommandLookupTopic -> FieldSet -> CommandLookupTopic)
-> Lens' CommandLookupTopic FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopic -> FieldSet
_CommandLookupTopic'_unknownFields
(\ x__ :: CommandLookupTopic
x__ y__ :: FieldSet
y__ -> CommandLookupTopic
x__ {_CommandLookupTopic'_unknownFields :: FieldSet
_CommandLookupTopic'_unknownFields = FieldSet
y__})
defMessage :: CommandLookupTopic
defMessage
= $WCommandLookupTopic'_constructor :: Text
-> Word64
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> FieldSet
-> CommandLookupTopic
CommandLookupTopic'_constructor
{_CommandLookupTopic'topic :: Text
_CommandLookupTopic'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandLookupTopic'requestId :: Word64
_CommandLookupTopic'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandLookupTopic'authoritative :: Maybe Bool
_CommandLookupTopic'authoritative = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopic'originalPrincipal :: Maybe Text
_CommandLookupTopic'originalPrincipal = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopic'originalAuthData :: Maybe Text
_CommandLookupTopic'originalAuthData = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopic'originalAuthMethod :: Maybe Text
_CommandLookupTopic'originalAuthMethod = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopic'advertisedListenerName :: Maybe Text
_CommandLookupTopic'advertisedListenerName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopic'_unknownFields :: FieldSet
_CommandLookupTopic'_unknownFields = []}
parseMessage :: Parser CommandLookupTopic
parseMessage
= let
loop ::
CommandLookupTopic
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandLookupTopic
loop :: CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop x :: CommandLookupTopic
x required'requestId :: Bool
required'requestId required'topic :: Bool
required'topic
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandLookupTopic -> Parser CommandLookupTopic
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandLookupTopic CommandLookupTopic FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandLookupTopic
-> CommandLookupTopic
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandLookupTopic CommandLookupTopic FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandLookupTopic
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Text Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandLookupTopic
x)
Bool
required'requestId
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Word64 Word64
-> Word64 -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandLookupTopic
x)
Bool
Prelude.False
Bool
required'topic
24
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"authoritative"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Bool Bool
-> Bool -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authoritative") Bool
y CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
34
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_principal"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Text Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalPrincipal") Text
y CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_data"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Text Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthData") Text
y CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
50
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_method"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Text Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthMethod") Text
y CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
58
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"advertised_listener_name"
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic Text Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "advertisedListenerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"advertisedListenerName") Text
y CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop
(Setter CommandLookupTopic CommandLookupTopic FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandLookupTopic
-> CommandLookupTopic
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandLookupTopic CommandLookupTopic FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandLookupTopic
x)
Bool
required'requestId
Bool
required'topic
in
Parser CommandLookupTopic -> String -> Parser CommandLookupTopic
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandLookupTopic -> Bool -> Bool -> Parser CommandLookupTopic
loop CommandLookupTopic
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandLookupTopic"
buildMessage :: CommandLookupTopic -> Builder
buildMessage
= \ _x :: CommandLookupTopic
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandLookupTopic CommandLookupTopic Text Text
-> CommandLookupTopic -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandLookupTopic
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandLookupTopic CommandLookupTopic Word64 Word64
-> CommandLookupTopic -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandLookupTopic
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandLookupTopic
CommandLookupTopic
(Maybe Bool)
(Maybe Bool)
-> CommandLookupTopic -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authoritative") CommandLookupTopic
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopic
CommandLookupTopic
(Maybe Text)
(Maybe Text)
-> CommandLookupTopic -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal") CommandLookupTopic
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopic
CommandLookupTopic
(Maybe Text)
(Maybe Text)
-> CommandLookupTopic -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData") CommandLookupTopic
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopic
CommandLookupTopic
(Maybe Text)
(Maybe Text)
-> CommandLookupTopic -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod") CommandLookupTopic
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopic
CommandLookupTopic
(Maybe Text)
(Maybe Text)
-> CommandLookupTopic -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'advertisedListenerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'advertisedListenerName")
CommandLookupTopic
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandLookupTopic CommandLookupTopic FieldSet FieldSet
-> CommandLookupTopic -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandLookupTopic CommandLookupTopic FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandLookupTopic
_x))))))))
instance Control.DeepSeq.NFData CommandLookupTopic where
rnf :: CommandLookupTopic -> ()
rnf
= \ x__ :: CommandLookupTopic
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> FieldSet
_CommandLookupTopic'_unknownFields CommandLookupTopic
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Text
_CommandLookupTopic'topic CommandLookupTopic
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Word64
_CommandLookupTopic'requestId CommandLookupTopic
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Maybe Bool
_CommandLookupTopic'authoritative CommandLookupTopic
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalPrincipal CommandLookupTopic
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthData CommandLookupTopic
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Maybe Text
_CommandLookupTopic'originalAuthMethod CommandLookupTopic
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopic -> Maybe Text
_CommandLookupTopic'advertisedListenerName CommandLookupTopic
x__) ())))))))
data CommandLookupTopicResponse
= CommandLookupTopicResponse'_constructor {CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response :: !(Prelude.Maybe CommandLookupTopicResponse'LookupType),
CommandLookupTopicResponse -> Word64
_CommandLookupTopicResponse'requestId :: !Data.Word.Word64,
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'authoritative :: !(Prelude.Maybe Prelude.Bool),
CommandLookupTopicResponse -> Maybe ServerError
_CommandLookupTopicResponse'error :: !(Prelude.Maybe ServerError),
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl :: !(Prelude.Maybe Prelude.Bool),
CommandLookupTopicResponse -> FieldSet
_CommandLookupTopicResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
(CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Bool)
-> Eq CommandLookupTopicResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c/= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
== :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c== :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
Prelude.Eq, Eq CommandLookupTopicResponse
Eq CommandLookupTopicResponse =>
(CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Ordering)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Bool)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Bool)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Bool)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Bool)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse)
-> (CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse)
-> Ord CommandLookupTopicResponse
CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Ordering
CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse
$cmin :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse
max :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse
$cmax :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> CommandLookupTopicResponse
>= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c>= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
> :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c> :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
<= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c<= :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
< :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
$c< :: CommandLookupTopicResponse -> CommandLookupTopicResponse -> Bool
compare :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Ordering
$ccompare :: CommandLookupTopicResponse
-> CommandLookupTopicResponse -> Ordering
$cp1Ord :: Eq CommandLookupTopicResponse
Prelude.Ord)
instance Prelude.Show CommandLookupTopicResponse where
showsPrec :: Int -> CommandLookupTopicResponse -> ShowS
showsPrec _ __x :: CommandLookupTopicResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandLookupTopicResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandLookupTopicResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "brokerServiceUrl" Data.Text.Text where
fieldOf :: Proxy# "brokerServiceUrl"
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'brokerServiceUrl :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'brokerServiceUrl" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'brokerServiceUrl"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'brokerServiceUrl :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "brokerServiceUrlTls" Data.Text.Text where
fieldOf :: Proxy# "brokerServiceUrlTls"
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'brokerServiceUrlTls :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'brokerServiceUrlTls" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'brokerServiceUrlTls"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'brokerServiceUrlTls :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "response" CommandLookupTopicResponse'LookupType where
fieldOf :: Proxy# "response"
-> (CommandLookupTopicResponse'LookupType
-> f CommandLookupTopicResponse'LookupType)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((CommandLookupTopicResponse'LookupType
-> f CommandLookupTopicResponse'LookupType)
-> Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> (CommandLookupTopicResponse'LookupType
-> f CommandLookupTopicResponse'LookupType)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType)
-> (CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe CommandLookupTopicResponse'LookupType)
(Maybe CommandLookupTopicResponse'LookupType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe CommandLookupTopicResponse'LookupType
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'response :: Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response = Maybe CommandLookupTopicResponse'LookupType
y__}))
(CommandLookupTopicResponse'LookupType
-> Lens'
(Maybe CommandLookupTopicResponse'LookupType)
CommandLookupTopicResponse'LookupType
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandLookupTopicResponse'LookupType
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'response" (Prelude.Maybe CommandLookupTopicResponse'LookupType) where
fieldOf :: Proxy# "maybe'response"
-> (Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> (Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType)
-> (CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe CommandLookupTopicResponse'LookupType)
(Maybe CommandLookupTopicResponse'LookupType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe CommandLookupTopicResponse'LookupType
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'response :: Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response = Maybe CommandLookupTopicResponse'LookupType
y__}))
(Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType))
-> Maybe CommandLookupTopicResponse'LookupType
-> f (Maybe CommandLookupTopicResponse'LookupType)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Word64)
-> (CommandLookupTopicResponse
-> Word64 -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse CommandLookupTopicResponse Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Word64
_CommandLookupTopicResponse'requestId
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Word64
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'requestId :: Word64
_CommandLookupTopicResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "authoritative" Prelude.Bool where
fieldOf :: Proxy# "authoritative"
-> (Bool -> f Bool)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Bool)
-> (CommandLookupTopicResponse
-> Maybe Bool -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'authoritative
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Bool
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'authoritative :: Maybe Bool
_CommandLookupTopicResponse'authoritative = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'authoritative" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'authoritative"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Bool)
-> (CommandLookupTopicResponse
-> Maybe Bool -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'authoritative
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Bool
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'authoritative :: Maybe Bool
_CommandLookupTopicResponse'authoritative = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe ServerError)
-> (CommandLookupTopicResponse
-> Maybe ServerError -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe ServerError
_CommandLookupTopicResponse'error
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe ServerError
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'error :: Maybe ServerError
_CommandLookupTopicResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe ServerError)
-> (CommandLookupTopicResponse
-> Maybe ServerError -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe ServerError
_CommandLookupTopicResponse'error
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe ServerError
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'error :: Maybe ServerError
_CommandLookupTopicResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'message
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'message :: Maybe Text
_CommandLookupTopicResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Text)
-> (CommandLookupTopicResponse
-> Maybe Text -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'message
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Text
y__ -> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'message :: Maybe Text
_CommandLookupTopicResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "proxyThroughServiceUrl" Prelude.Bool where
fieldOf :: Proxy# "proxyThroughServiceUrl"
-> (Bool -> f Bool)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Bool)
-> (CommandLookupTopicResponse
-> Maybe Bool -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Bool
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'proxyThroughServiceUrl :: Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandLookupTopicResponse "maybe'proxyThroughServiceUrl" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'proxyThroughServiceUrl"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse -> f CommandLookupTopicResponse)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandLookupTopicResponse
-> f CommandLookupTopicResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandLookupTopicResponse -> Maybe Bool)
-> (CommandLookupTopicResponse
-> Maybe Bool -> CommandLookupTopicResponse)
-> Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: Maybe Bool
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'proxyThroughServiceUrl :: Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandLookupTopicResponse where
messageName :: Proxy CommandLookupTopicResponse -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandLookupTopicResponse"
packedMessageDescriptor :: Proxy CommandLookupTopicResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\SUBCommandLookupTopicResponse\DC2*\n\
\\DLEbrokerServiceUrl\CAN\SOH \SOH(\tR\DLEbrokerServiceUrl\DC20\n\
\\DC3brokerServiceUrlTls\CAN\STX \SOH(\tR\DC3brokerServiceUrlTls\DC2O\n\
\\bresponse\CAN\ETX \SOH(\SO23.pulsar.proto.CommandLookupTopicResponse.LookupTypeR\bresponse\DC2\GS\n\
\\n\
\request_id\CAN\EOT \STX(\EOTR\trequestId\DC2+\n\
\\rauthoritative\CAN\ENQ \SOH(\b:\ENQfalseR\rauthoritative\DC2/\n\
\\ENQerror\CAN\ACK \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\a \SOH(\tR\amessage\DC2@\n\
\\EMproxy_through_service_url\CAN\b \SOH(\b:\ENQfalseR\SYNproxyThroughServiceUrl\"3\n\
\\n\
\LookupType\DC2\f\n\
\\bRedirect\DLE\NUL\DC2\v\n\
\\aConnect\DLE\SOH\DC2\n\
\\n\
\\ACKFailed\DLE\STX"
packedFileDescriptor :: Proxy CommandLookupTopicResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandLookupTopicResponse)
fieldsByTag
= let
brokerServiceUrl__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
brokerServiceUrl__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopicResponse Text
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"brokerServiceUrl"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandLookupTopicResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'brokerServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'brokerServiceUrl")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
brokerServiceUrlTls__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
brokerServiceUrlTls__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopicResponse Text
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"brokerServiceUrlTls"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandLookupTopicResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'brokerServiceUrlTls" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'brokerServiceUrlTls")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
response__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
response__field_descriptor
= String
-> FieldTypeDescriptor CommandLookupTopicResponse'LookupType
-> FieldAccessor
CommandLookupTopicResponse CommandLookupTopicResponse'LookupType
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"response"
(ScalarField CommandLookupTopicResponse'LookupType
-> FieldTypeDescriptor CommandLookupTopicResponse'LookupType
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandLookupTopicResponse'LookupType
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandLookupTopicResponse'LookupType)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe CommandLookupTopicResponse'LookupType)
(Maybe CommandLookupTopicResponse'LookupType)
-> FieldAccessor
CommandLookupTopicResponse CommandLookupTopicResponse'LookupType
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
requestId__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandLookupTopicResponse Word64
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandLookupTopicResponse CommandLookupTopicResponse Word64 Word64
-> FieldAccessor CommandLookupTopicResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
authoritative__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
authoritative__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandLookupTopicResponse Bool
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"authoritative"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor CommandLookupTopicResponse Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authoritative")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
error__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandLookupTopicResponse ServerError
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandLookupTopicResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
message__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandLookupTopicResponse Text
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandLookupTopicResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
proxyThroughServiceUrl__field_descriptor :: FieldDescriptor CommandLookupTopicResponse
proxyThroughServiceUrl__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandLookupTopicResponse Bool
-> FieldDescriptor CommandLookupTopicResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"proxy_through_service_url"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor CommandLookupTopicResponse Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'proxyThroughServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'proxyThroughServiceUrl")) ::
Data.ProtoLens.FieldDescriptor CommandLookupTopicResponse
in
[(Tag, FieldDescriptor CommandLookupTopicResponse)]
-> Map Tag (FieldDescriptor CommandLookupTopicResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandLookupTopicResponse
brokerServiceUrl__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandLookupTopicResponse
brokerServiceUrlTls__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandLookupTopicResponse
response__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandLookupTopicResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandLookupTopicResponse
authoritative__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandLookupTopicResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandLookupTopicResponse
message__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor CommandLookupTopicResponse
proxyThroughServiceUrl__field_descriptor)]
unknownFields :: LensLike' f CommandLookupTopicResponse FieldSet
unknownFields
= (CommandLookupTopicResponse -> FieldSet)
-> (CommandLookupTopicResponse
-> FieldSet -> CommandLookupTopicResponse)
-> Lens' CommandLookupTopicResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandLookupTopicResponse -> FieldSet
_CommandLookupTopicResponse'_unknownFields
(\ x__ :: CommandLookupTopicResponse
x__ y__ :: FieldSet
y__
-> CommandLookupTopicResponse
x__ {_CommandLookupTopicResponse'_unknownFields :: FieldSet
_CommandLookupTopicResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandLookupTopicResponse
defMessage
= $WCommandLookupTopicResponse'_constructor :: Maybe Text
-> Maybe Text
-> Maybe CommandLookupTopicResponse'LookupType
-> Word64
-> Maybe Bool
-> Maybe ServerError
-> Maybe Text
-> Maybe Bool
-> FieldSet
-> CommandLookupTopicResponse
CommandLookupTopicResponse'_constructor
{_CommandLookupTopicResponse'brokerServiceUrl :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'brokerServiceUrlTls :: Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'response :: Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response = Maybe CommandLookupTopicResponse'LookupType
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'requestId :: Word64
_CommandLookupTopicResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandLookupTopicResponse'authoritative :: Maybe Bool
_CommandLookupTopicResponse'authoritative = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'error :: Maybe ServerError
_CommandLookupTopicResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'message :: Maybe Text
_CommandLookupTopicResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'proxyThroughServiceUrl :: Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandLookupTopicResponse'_unknownFields :: FieldSet
_CommandLookupTopicResponse'_unknownFields = []}
parseMessage :: Parser CommandLookupTopicResponse
parseMessage
= let
loop ::
CommandLookupTopicResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandLookupTopicResponse
loop :: CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop x :: CommandLookupTopicResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandLookupTopicResponse -> Parser CommandLookupTopicResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandLookupTopicResponse
-> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandLookupTopicResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"brokerServiceUrl"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Text Text
-> Text -> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "brokerServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"brokerServiceUrl") Text
y CommandLookupTopicResponse
x)
Bool
required'requestId
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"brokerServiceUrlTls"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Text Text
-> Text -> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "brokerServiceUrlTls" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"brokerServiceUrlTls") Text
y CommandLookupTopicResponse
x)
Bool
required'requestId
24
-> do CommandLookupTopicResponse'LookupType
y <- Parser CommandLookupTopicResponse'LookupType
-> String -> Parser CommandLookupTopicResponse'LookupType
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandLookupTopicResponse'LookupType)
-> Parser Int -> Parser CommandLookupTopicResponse'LookupType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandLookupTopicResponse'LookupType
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"response"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse
-> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"response") CommandLookupTopicResponse'LookupType
y CommandLookupTopicResponse
x)
Bool
required'requestId
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Word64 Word64
-> Word64
-> CommandLookupTopicResponse
-> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandLookupTopicResponse
x)
Bool
Prelude.False
40
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"authoritative"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Bool Bool
-> Bool -> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"authoritative") Bool
y CommandLookupTopicResponse
x)
Bool
required'requestId
48
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
ServerError
ServerError
-> ServerError
-> CommandLookupTopicResponse
-> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandLookupTopicResponse
x)
Bool
required'requestId
58
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Text Text
-> Text -> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandLookupTopicResponse
x)
Bool
required'requestId
64
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"proxy_through_service_url"
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse CommandLookupTopicResponse Bool Bool
-> Bool -> CommandLookupTopicResponse -> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "proxyThroughServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"proxyThroughServiceUrl") Bool
y CommandLookupTopicResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop
(Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandLookupTopicResponse
-> CommandLookupTopicResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandLookupTopicResponse
x)
Bool
required'requestId
in
Parser CommandLookupTopicResponse
-> String -> Parser CommandLookupTopicResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandLookupTopicResponse
-> Bool -> Parser CommandLookupTopicResponse
loop CommandLookupTopicResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandLookupTopicResponse"
buildMessage :: CommandLookupTopicResponse -> Builder
buildMessage
= \ _x :: CommandLookupTopicResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> CommandLookupTopicResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'brokerServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'brokerServiceUrl") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> CommandLookupTopicResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'brokerServiceUrlTls" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'brokerServiceUrlTls") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandLookupTopicResponse'LookupType)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe CommandLookupTopicResponse'LookupType)
(Maybe CommandLookupTopicResponse'LookupType)
-> CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandLookupTopicResponse'LookupType
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Int -> Builder)
-> (CommandLookupTopicResponse'LookupType -> Int)
-> CommandLookupTopicResponse'LookupType
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandLookupTopicResponse'LookupType -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CommandLookupTopicResponse'LookupType
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandLookupTopicResponse
CommandLookupTopicResponse
Word64
Word64
-> CommandLookupTopicResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandLookupTopicResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
-> CommandLookupTopicResponse -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'authoritative" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'authoritative") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandLookupTopicResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 48)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Text)
(Maybe Text)
-> CommandLookupTopicResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandLookupTopicResponse
CommandLookupTopicResponse
(Maybe Bool)
(Maybe Bool)
-> CommandLookupTopicResponse -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'proxyThroughServiceUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'proxyThroughServiceUrl")
CommandLookupTopicResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
-> CommandLookupTopicResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandLookupTopicResponse
CommandLookupTopicResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandLookupTopicResponse
_x)))))))))
instance Control.DeepSeq.NFData CommandLookupTopicResponse where
rnf :: CommandLookupTopicResponse -> ()
rnf
= \ x__ :: CommandLookupTopicResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> FieldSet
_CommandLookupTopicResponse'_unknownFields CommandLookupTopicResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrl CommandLookupTopicResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'brokerServiceUrlTls CommandLookupTopicResponse
x__)
(Maybe CommandLookupTopicResponse'LookupType -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse
-> Maybe CommandLookupTopicResponse'LookupType
_CommandLookupTopicResponse'response CommandLookupTopicResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Word64
_CommandLookupTopicResponse'requestId CommandLookupTopicResponse
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'authoritative CommandLookupTopicResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe ServerError
_CommandLookupTopicResponse'error CommandLookupTopicResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe Text
_CommandLookupTopicResponse'message CommandLookupTopicResponse
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandLookupTopicResponse -> Maybe Bool
_CommandLookupTopicResponse'proxyThroughServiceUrl CommandLookupTopicResponse
x__)
()))))))))
data CommandLookupTopicResponse'LookupType
= CommandLookupTopicResponse'Redirect |
CommandLookupTopicResponse'Connect |
CommandLookupTopicResponse'Failed
deriving stock (Int -> CommandLookupTopicResponse'LookupType -> ShowS
[CommandLookupTopicResponse'LookupType] -> ShowS
CommandLookupTopicResponse'LookupType -> String
(Int -> CommandLookupTopicResponse'LookupType -> ShowS)
-> (CommandLookupTopicResponse'LookupType -> String)
-> ([CommandLookupTopicResponse'LookupType] -> ShowS)
-> Show CommandLookupTopicResponse'LookupType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandLookupTopicResponse'LookupType] -> ShowS
$cshowList :: [CommandLookupTopicResponse'LookupType] -> ShowS
show :: CommandLookupTopicResponse'LookupType -> String
$cshow :: CommandLookupTopicResponse'LookupType -> String
showsPrec :: Int -> CommandLookupTopicResponse'LookupType -> ShowS
$cshowsPrec :: Int -> CommandLookupTopicResponse'LookupType -> ShowS
Prelude.Show, CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
(CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> Eq CommandLookupTopicResponse'LookupType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c/= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
== :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c== :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
Prelude.Eq, Eq CommandLookupTopicResponse'LookupType
Eq CommandLookupTopicResponse'LookupType =>
(CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Ordering)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType)
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType)
-> Ord CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Ordering
CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
$cmin :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
max :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
$cmax :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
>= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c>= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
> :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c> :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
<= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c<= :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
< :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
$c< :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Bool
compare :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Ordering
$ccompare :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType -> Ordering
$cp1Ord :: Eq CommandLookupTopicResponse'LookupType
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandLookupTopicResponse'LookupType where
maybeToEnum :: Int -> Maybe CommandLookupTopicResponse'LookupType
maybeToEnum 0 = CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Redirect
maybeToEnum 1 = CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Connect
maybeToEnum 2 = CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Failed
maybeToEnum _ = Maybe CommandLookupTopicResponse'LookupType
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandLookupTopicResponse'LookupType -> String
showEnum CommandLookupTopicResponse'Redirect = "Redirect"
showEnum CommandLookupTopicResponse'Connect = "Connect"
showEnum CommandLookupTopicResponse'Failed = "Failed"
readEnum :: String -> Maybe CommandLookupTopicResponse'LookupType
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Redirect"
= CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Redirect
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Connect"
= CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Connect
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Failed"
= CommandLookupTopicResponse'LookupType
-> Maybe CommandLookupTopicResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Failed
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandLookupTopicResponse'LookupType)
-> Maybe CommandLookupTopicResponse'LookupType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandLookupTopicResponse'LookupType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandLookupTopicResponse'LookupType where
minBound :: CommandLookupTopicResponse'LookupType
minBound = CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Redirect
maxBound :: CommandLookupTopicResponse'LookupType
maxBound = CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Failed
instance Prelude.Enum CommandLookupTopicResponse'LookupType where
toEnum :: Int -> CommandLookupTopicResponse'LookupType
toEnum k__ :: Int
k__
= CommandLookupTopicResponse'LookupType
-> (CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType)
-> Maybe CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandLookupTopicResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum LookupType: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
forall a. a -> a
Prelude.id
(Int -> Maybe CommandLookupTopicResponse'LookupType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandLookupTopicResponse'LookupType -> Int
fromEnum CommandLookupTopicResponse'Redirect = 0
fromEnum CommandLookupTopicResponse'Connect = 1
fromEnum CommandLookupTopicResponse'Failed = 2
succ :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
succ CommandLookupTopicResponse'Failed
= String -> CommandLookupTopicResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
"CommandLookupTopicResponse'LookupType.succ: bad argument CommandLookupTopicResponse'Failed. This value would be out of bounds."
succ CommandLookupTopicResponse'Redirect
= CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Connect
succ CommandLookupTopicResponse'Connect
= CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Failed
pred :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
pred CommandLookupTopicResponse'Redirect
= String -> CommandLookupTopicResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
"CommandLookupTopicResponse'LookupType.pred: bad argument CommandLookupTopicResponse'Redirect. This value would be out of bounds."
pred CommandLookupTopicResponse'Connect
= CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Redirect
pred CommandLookupTopicResponse'Failed
= CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Connect
enumFrom :: CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
enumFrom = CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
enumFromTo = CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
enumFromThen = CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
enumFromThenTo = CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> CommandLookupTopicResponse'LookupType
-> [CommandLookupTopicResponse'LookupType]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandLookupTopicResponse'LookupType where
fieldDefault :: CommandLookupTopicResponse'LookupType
fieldDefault = CommandLookupTopicResponse'LookupType
CommandLookupTopicResponse'Redirect
instance Control.DeepSeq.NFData CommandLookupTopicResponse'LookupType where
rnf :: CommandLookupTopicResponse'LookupType -> ()
rnf x__ :: CommandLookupTopicResponse'LookupType
x__ = CommandLookupTopicResponse'LookupType -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandLookupTopicResponse'LookupType
x__ ()
data CommandMessage
= CommandMessage'_constructor {CommandMessage -> Word64
_CommandMessage'consumerId :: !Data.Word.Word64,
CommandMessage -> MessageIdData
_CommandMessage'messageId :: !MessageIdData,
CommandMessage -> Maybe Word32
_CommandMessage'redeliveryCount :: !(Prelude.Maybe Data.Word.Word32),
CommandMessage -> Vector Int64
_CommandMessage'ackSet :: !(Data.Vector.Unboxed.Vector Data.Int.Int64),
CommandMessage -> FieldSet
_CommandMessage'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandMessage -> CommandMessage -> Bool
(CommandMessage -> CommandMessage -> Bool)
-> (CommandMessage -> CommandMessage -> Bool) -> Eq CommandMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandMessage -> CommandMessage -> Bool
$c/= :: CommandMessage -> CommandMessage -> Bool
== :: CommandMessage -> CommandMessage -> Bool
$c== :: CommandMessage -> CommandMessage -> Bool
Prelude.Eq, Eq CommandMessage
Eq CommandMessage =>
(CommandMessage -> CommandMessage -> Ordering)
-> (CommandMessage -> CommandMessage -> Bool)
-> (CommandMessage -> CommandMessage -> Bool)
-> (CommandMessage -> CommandMessage -> Bool)
-> (CommandMessage -> CommandMessage -> Bool)
-> (CommandMessage -> CommandMessage -> CommandMessage)
-> (CommandMessage -> CommandMessage -> CommandMessage)
-> Ord CommandMessage
CommandMessage -> CommandMessage -> Bool
CommandMessage -> CommandMessage -> Ordering
CommandMessage -> CommandMessage -> CommandMessage
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandMessage -> CommandMessage -> CommandMessage
$cmin :: CommandMessage -> CommandMessage -> CommandMessage
max :: CommandMessage -> CommandMessage -> CommandMessage
$cmax :: CommandMessage -> CommandMessage -> CommandMessage
>= :: CommandMessage -> CommandMessage -> Bool
$c>= :: CommandMessage -> CommandMessage -> Bool
> :: CommandMessage -> CommandMessage -> Bool
$c> :: CommandMessage -> CommandMessage -> Bool
<= :: CommandMessage -> CommandMessage -> Bool
$c<= :: CommandMessage -> CommandMessage -> Bool
< :: CommandMessage -> CommandMessage -> Bool
$c< :: CommandMessage -> CommandMessage -> Bool
compare :: CommandMessage -> CommandMessage -> Ordering
$ccompare :: CommandMessage -> CommandMessage -> Ordering
$cp1Ord :: Eq CommandMessage
Prelude.Ord)
instance Prelude.Show CommandMessage where
showsPrec :: Int -> CommandMessage -> ShowS
showsPrec _ __x :: CommandMessage
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandMessage -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandMessage
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandMessage "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64) -> CommandMessage -> f CommandMessage
fieldOf _
= ((Word64 -> f Word64) -> CommandMessage -> f CommandMessage)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> Word64)
-> (CommandMessage -> Word64 -> CommandMessage)
-> Lens CommandMessage CommandMessage Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> Word64
_CommandMessage'consumerId
(\ x__ :: CommandMessage
x__ y__ :: Word64
y__ -> CommandMessage
x__ {_CommandMessage'consumerId :: Word64
_CommandMessage'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandMessage "messageId" MessageIdData where
fieldOf :: Proxy# "messageId"
-> (MessageIdData -> f MessageIdData)
-> CommandMessage
-> f CommandMessage
fieldOf _
= ((MessageIdData -> f MessageIdData)
-> CommandMessage -> f CommandMessage)
-> ((MessageIdData -> f MessageIdData)
-> MessageIdData -> f MessageIdData)
-> (MessageIdData -> f MessageIdData)
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> MessageIdData)
-> (CommandMessage -> MessageIdData -> CommandMessage)
-> Lens CommandMessage CommandMessage MessageIdData MessageIdData
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> MessageIdData
_CommandMessage'messageId
(\ x__ :: CommandMessage
x__ y__ :: MessageIdData
y__ -> CommandMessage
x__ {_CommandMessage'messageId :: MessageIdData
_CommandMessage'messageId = MessageIdData
y__}))
(MessageIdData -> f MessageIdData)
-> MessageIdData -> f MessageIdData
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandMessage "redeliveryCount" Data.Word.Word32 where
fieldOf :: Proxy# "redeliveryCount"
-> (Word32 -> f Word32) -> CommandMessage -> f CommandMessage
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> CommandMessage -> f CommandMessage)
-> ((Word32 -> f Word32) -> Maybe Word32 -> f (Maybe Word32))
-> (Word32 -> f Word32)
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> Maybe Word32)
-> (CommandMessage -> Maybe Word32 -> CommandMessage)
-> Lens CommandMessage CommandMessage (Maybe Word32) (Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> Maybe Word32
_CommandMessage'redeliveryCount
(\ x__ :: CommandMessage
x__ y__ :: Maybe Word32
y__ -> CommandMessage
x__ {_CommandMessage'redeliveryCount :: Maybe Word32
_CommandMessage'redeliveryCount = Maybe Word32
y__}))
(Word32 -> Lens' (Maybe Word32) Word32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandMessage "maybe'redeliveryCount" (Prelude.Maybe Data.Word.Word32) where
fieldOf :: Proxy# "maybe'redeliveryCount"
-> (Maybe Word32 -> f (Maybe Word32))
-> CommandMessage
-> f CommandMessage
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> CommandMessage -> f CommandMessage)
-> ((Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32))
-> (Maybe Word32 -> f (Maybe Word32))
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> Maybe Word32)
-> (CommandMessage -> Maybe Word32 -> CommandMessage)
-> Lens CommandMessage CommandMessage (Maybe Word32) (Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> Maybe Word32
_CommandMessage'redeliveryCount
(\ x__ :: CommandMessage
x__ y__ :: Maybe Word32
y__ -> CommandMessage
x__ {_CommandMessage'redeliveryCount :: Maybe Word32
_CommandMessage'redeliveryCount = Maybe Word32
y__}))
(Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandMessage "ackSet" [Data.Int.Int64] where
fieldOf :: Proxy# "ackSet"
-> ([Int64] -> f [Int64]) -> CommandMessage -> f CommandMessage
fieldOf _
= ((Vector Int64 -> f (Vector Int64))
-> CommandMessage -> f CommandMessage)
-> (([Int64] -> f [Int64]) -> Vector Int64 -> f (Vector Int64))
-> ([Int64] -> f [Int64])
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> Vector Int64)
-> (CommandMessage -> Vector Int64 -> CommandMessage)
-> Lens CommandMessage CommandMessage (Vector Int64) (Vector Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> Vector Int64
_CommandMessage'ackSet
(\ x__ :: CommandMessage
x__ y__ :: Vector Int64
y__ -> CommandMessage
x__ {_CommandMessage'ackSet :: Vector Int64
_CommandMessage'ackSet = Vector Int64
y__}))
((Vector Int64 -> [Int64])
-> (Vector Int64 -> [Int64] -> Vector Int64)
-> Lens (Vector Int64) (Vector Int64) [Int64] [Int64]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Int64 -> [Int64]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Int64]
y__ -> [Int64] -> Vector Int64
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Int64]
y__))
instance Data.ProtoLens.Field.HasField CommandMessage "vec'ackSet" (Data.Vector.Unboxed.Vector Data.Int.Int64) where
fieldOf :: Proxy# "vec'ackSet"
-> (Vector Int64 -> f (Vector Int64))
-> CommandMessage
-> f CommandMessage
fieldOf _
= ((Vector Int64 -> f (Vector Int64))
-> CommandMessage -> f CommandMessage)
-> ((Vector Int64 -> f (Vector Int64))
-> Vector Int64 -> f (Vector Int64))
-> (Vector Int64 -> f (Vector Int64))
-> CommandMessage
-> f CommandMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandMessage -> Vector Int64)
-> (CommandMessage -> Vector Int64 -> CommandMessage)
-> Lens CommandMessage CommandMessage (Vector Int64) (Vector Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> Vector Int64
_CommandMessage'ackSet
(\ x__ :: CommandMessage
x__ y__ :: Vector Int64
y__ -> CommandMessage
x__ {_CommandMessage'ackSet :: Vector Int64
_CommandMessage'ackSet = Vector Int64
y__}))
(Vector Int64 -> f (Vector Int64))
-> Vector Int64 -> f (Vector Int64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandMessage where
messageName :: Proxy CommandMessage -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandMessage"
packedMessageDescriptor :: Proxy CommandMessage -> ByteString
packedMessageDescriptor _
= "\n\
\\SOCommandMessage\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2:\n\
\\n\
\message_id\CAN\STX \STX(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC2,\n\
\\DLEredelivery_count\CAN\ETX \SOH(\r:\SOH0R\SIredeliveryCount\DC2\ETB\n\
\\aack_set\CAN\EOT \ETX(\ETXR\ACKackSet"
packedFileDescriptor :: Proxy CommandMessage -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandMessage)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandMessage
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandMessage Word64
-> FieldDescriptor CommandMessage
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandMessage CommandMessage Word64 Word64
-> FieldAccessor CommandMessage Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandMessage
messageId__field_descriptor :: FieldDescriptor CommandMessage
messageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandMessage MessageIdData
-> FieldDescriptor CommandMessage
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(WireDefault MessageIdData
-> Lens CommandMessage CommandMessage MessageIdData MessageIdData
-> FieldAccessor CommandMessage MessageIdData
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault MessageIdData
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId")) ::
Data.ProtoLens.FieldDescriptor CommandMessage
redeliveryCount__field_descriptor :: FieldDescriptor CommandMessage
redeliveryCount__field_descriptor
= String
-> FieldTypeDescriptor Word32
-> FieldAccessor CommandMessage Word32
-> FieldDescriptor CommandMessage
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"redelivery_count"
(ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
(Lens CommandMessage CommandMessage (Maybe Word32) (Maybe Word32)
-> FieldAccessor CommandMessage Word32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'redeliveryCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'redeliveryCount")) ::
Data.ProtoLens.FieldDescriptor CommandMessage
ackSet__field_descriptor :: FieldDescriptor CommandMessage
ackSet__field_descriptor
= String
-> FieldTypeDescriptor Int64
-> FieldAccessor CommandMessage Int64
-> FieldDescriptor CommandMessage
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ack_set"
(ScalarField Int64 -> FieldTypeDescriptor Int64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int64
Data.ProtoLens.Int64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int64)
(Packing
-> Lens' CommandMessage [Int64]
-> FieldAccessor CommandMessage Int64
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackSet")) ::
Data.ProtoLens.FieldDescriptor CommandMessage
in
[(Tag, FieldDescriptor CommandMessage)]
-> Map Tag (FieldDescriptor CommandMessage)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandMessage
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandMessage
messageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandMessage
redeliveryCount__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandMessage
ackSet__field_descriptor)]
unknownFields :: LensLike' f CommandMessage FieldSet
unknownFields
= (CommandMessage -> FieldSet)
-> (CommandMessage -> FieldSet -> CommandMessage)
-> Lens' CommandMessage FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandMessage -> FieldSet
_CommandMessage'_unknownFields
(\ x__ :: CommandMessage
x__ y__ :: FieldSet
y__ -> CommandMessage
x__ {_CommandMessage'_unknownFields :: FieldSet
_CommandMessage'_unknownFields = FieldSet
y__})
defMessage :: CommandMessage
defMessage
= $WCommandMessage'_constructor :: Word64
-> MessageIdData
-> Maybe Word32
-> Vector Int64
-> FieldSet
-> CommandMessage
CommandMessage'_constructor
{_CommandMessage'consumerId :: Word64
_CommandMessage'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandMessage'messageId :: MessageIdData
_CommandMessage'messageId = MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage,
_CommandMessage'redeliveryCount :: Maybe Word32
_CommandMessage'redeliveryCount = Maybe Word32
forall a. Maybe a
Prelude.Nothing,
_CommandMessage'ackSet :: Vector Int64
_CommandMessage'ackSet = Vector Int64
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandMessage'_unknownFields :: FieldSet
_CommandMessage'_unknownFields = []}
parseMessage :: Parser CommandMessage
parseMessage
= let
loop ::
CommandMessage
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Unboxed.Vector Data.ProtoLens.Encoding.Growing.RealWorld Data.Int.Int64
-> Data.ProtoLens.Encoding.Bytes.Parser CommandMessage
loop :: CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop x :: CommandMessage
x required'consumerId :: Bool
required'consumerId required'messageId :: Bool
required'messageId mutable'ackSet :: Growing Vector RealWorld Int64
mutable'ackSet
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector Int64
frozen'ackSet <- IO (Vector Int64) -> Parser (Vector Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Int64 -> IO (Vector Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Int64
Growing Vector (PrimState IO) Int64
mutable'ackSet)
(let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'messageId then (:) "message_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandMessage -> Parser CommandMessage
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandMessage CommandMessage FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandMessage CommandMessage FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter CommandMessage CommandMessage (Vector Int64) (Vector Int64)
-> Vector Int64 -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ackSet") Vector Int64
frozen'ackSet CommandMessage
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop
(Setter CommandMessage CommandMessage Word64 Word64
-> Word64 -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandMessage
x)
Bool
Prelude.False
Bool
required'messageId
Growing Vector RealWorld Int64
mutable'ackSet
18
-> do MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message_id"
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop
(Setter CommandMessage CommandMessage MessageIdData MessageIdData
-> MessageIdData -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId") MessageIdData
y CommandMessage
x)
Bool
required'consumerId
Bool
Prelude.False
Growing Vector RealWorld Int64
mutable'ackSet
24
-> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"redelivery_count"
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop
(Setter CommandMessage CommandMessage Word32 Word32
-> Word32 -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "redeliveryCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"redeliveryCount") Word32
y CommandMessage
x)
Bool
required'consumerId
Bool
required'messageId
Growing Vector RealWorld Int64
mutable'ackSet
32
-> do !Int64
y <- Parser Int64 -> String -> Parser Int64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int64) -> Parser Word64 -> Parser Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"ack_set"
Growing Vector RealWorld Int64
v <- IO (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Int64
-> Int64 -> IO (Growing Vector (PrimState IO) Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Int64
Growing Vector (PrimState IO) Int64
mutable'ackSet Int64
y)
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop CommandMessage
x Bool
required'consumerId Bool
required'messageId Growing Vector RealWorld Int64
v
34
-> do Growing Vector RealWorld Int64
y <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
((let
ploop :: Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop qs :: Growing v RealWorld a
qs
= do Bool
packedEnd <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
packedEnd then
Growing v RealWorld a -> Parser (Growing v RealWorld a)
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return Growing v RealWorld a
qs
else
do !a
q <- Parser a -> String -> Parser a
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> a) -> Parser Word64 -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> a
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"ack_set"
Growing v RealWorld a
qs' <- IO (Growing v RealWorld a) -> Parser (Growing v RealWorld a)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing v (PrimState IO) a -> a -> IO (Growing v (PrimState IO) a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
Growing v RealWorld a
Growing v (PrimState IO) a
qs a
q)
Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop Growing v RealWorld a
qs'
in forall a (v :: * -> *).
(Num a, Vector v a) =>
Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop)
Growing Vector RealWorld Int64
mutable'ackSet)
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop CommandMessage
x Bool
required'consumerId Bool
required'messageId Growing Vector RealWorld Int64
y
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop
(Setter CommandMessage CommandMessage FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandMessage -> CommandMessage
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandMessage CommandMessage FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandMessage
x)
Bool
required'consumerId
Bool
required'messageId
Growing Vector RealWorld Int64
mutable'ackSet
in
Parser CommandMessage -> String -> Parser CommandMessage
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld Int64
mutable'ackSet <- IO (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandMessage
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser CommandMessage
loop
CommandMessage
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True Growing Vector RealWorld Int64
mutable'ackSet)
"CommandMessage"
buildMessage :: CommandMessage -> Builder
buildMessage
= \ _x :: CommandMessage
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandMessage CommandMessage Word64 Word64
-> CommandMessage -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandMessage
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
(FoldLike
MessageIdData
CommandMessage
CommandMessage
MessageIdData
MessageIdData
-> CommandMessage -> MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId") CommandMessage
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word32)
CommandMessage
CommandMessage
(Maybe Word32)
(Maybe Word32)
-> CommandMessage -> Maybe Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'redeliveryCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'redeliveryCount") CommandMessage
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Int64 -> Builder) -> Vector Int64 -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Int64
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Word64 -> Builder) -> (Int64 -> Word64) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int64
_v))
(FoldLike
(Vector Int64)
CommandMessage
CommandMessage
(Vector Int64)
(Vector Int64)
-> CommandMessage -> Vector Int64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "vec'ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ackSet") CommandMessage
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandMessage CommandMessage FieldSet FieldSet
-> CommandMessage -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandMessage CommandMessage FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandMessage
_x)))))
instance Control.DeepSeq.NFData CommandMessage where
rnf :: CommandMessage -> ()
rnf
= \ x__ :: CommandMessage
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandMessage -> FieldSet
_CommandMessage'_unknownFields CommandMessage
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandMessage -> Word64
_CommandMessage'consumerId CommandMessage
x__)
(MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandMessage -> MessageIdData
_CommandMessage'messageId CommandMessage
x__)
(Maybe Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandMessage -> Maybe Word32
_CommandMessage'redeliveryCount CommandMessage
x__)
(Vector Int64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandMessage -> Vector Int64
_CommandMessage'ackSet CommandMessage
x__) ()))))
data CommandNewTxn
= CommandNewTxn'_constructor {CommandNewTxn -> Word64
_CommandNewTxn'requestId :: !Data.Word.Word64,
CommandNewTxn -> Maybe Word64
_CommandNewTxn'txnTtlSeconds :: !(Prelude.Maybe Data.Word.Word64),
CommandNewTxn -> Maybe Word64
_CommandNewTxn'tcId :: !(Prelude.Maybe Data.Word.Word64),
CommandNewTxn -> FieldSet
_CommandNewTxn'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandNewTxn -> CommandNewTxn -> Bool
(CommandNewTxn -> CommandNewTxn -> Bool)
-> (CommandNewTxn -> CommandNewTxn -> Bool) -> Eq CommandNewTxn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandNewTxn -> CommandNewTxn -> Bool
$c/= :: CommandNewTxn -> CommandNewTxn -> Bool
== :: CommandNewTxn -> CommandNewTxn -> Bool
$c== :: CommandNewTxn -> CommandNewTxn -> Bool
Prelude.Eq, Eq CommandNewTxn
Eq CommandNewTxn =>
(CommandNewTxn -> CommandNewTxn -> Ordering)
-> (CommandNewTxn -> CommandNewTxn -> Bool)
-> (CommandNewTxn -> CommandNewTxn -> Bool)
-> (CommandNewTxn -> CommandNewTxn -> Bool)
-> (CommandNewTxn -> CommandNewTxn -> Bool)
-> (CommandNewTxn -> CommandNewTxn -> CommandNewTxn)
-> (CommandNewTxn -> CommandNewTxn -> CommandNewTxn)
-> Ord CommandNewTxn
CommandNewTxn -> CommandNewTxn -> Bool
CommandNewTxn -> CommandNewTxn -> Ordering
CommandNewTxn -> CommandNewTxn -> CommandNewTxn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandNewTxn -> CommandNewTxn -> CommandNewTxn
$cmin :: CommandNewTxn -> CommandNewTxn -> CommandNewTxn
max :: CommandNewTxn -> CommandNewTxn -> CommandNewTxn
$cmax :: CommandNewTxn -> CommandNewTxn -> CommandNewTxn
>= :: CommandNewTxn -> CommandNewTxn -> Bool
$c>= :: CommandNewTxn -> CommandNewTxn -> Bool
> :: CommandNewTxn -> CommandNewTxn -> Bool
$c> :: CommandNewTxn -> CommandNewTxn -> Bool
<= :: CommandNewTxn -> CommandNewTxn -> Bool
$c<= :: CommandNewTxn -> CommandNewTxn -> Bool
< :: CommandNewTxn -> CommandNewTxn -> Bool
$c< :: CommandNewTxn -> CommandNewTxn -> Bool
compare :: CommandNewTxn -> CommandNewTxn -> Ordering
$ccompare :: CommandNewTxn -> CommandNewTxn -> Ordering
$cp1Ord :: Eq CommandNewTxn
Prelude.Ord)
instance Prelude.Show CommandNewTxn where
showsPrec :: Int -> CommandNewTxn -> ShowS
showsPrec _ __x :: CommandNewTxn
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandNewTxn -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandNewTxn
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandNewTxn "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandNewTxn -> f CommandNewTxn
fieldOf _
= ((Word64 -> f Word64) -> CommandNewTxn -> f CommandNewTxn)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandNewTxn
-> f CommandNewTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxn -> Word64)
-> (CommandNewTxn -> Word64 -> CommandNewTxn)
-> Lens CommandNewTxn CommandNewTxn Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> Word64
_CommandNewTxn'requestId
(\ x__ :: CommandNewTxn
x__ y__ :: Word64
y__ -> CommandNewTxn
x__ {_CommandNewTxn'requestId :: Word64
_CommandNewTxn'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxn "txnTtlSeconds" Data.Word.Word64 where
fieldOf :: Proxy# "txnTtlSeconds"
-> (Word64 -> f Word64) -> CommandNewTxn -> f CommandNewTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn -> f CommandNewTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandNewTxn
-> f CommandNewTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxn -> Maybe Word64)
-> (CommandNewTxn -> Maybe Word64 -> CommandNewTxn)
-> Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> Maybe Word64
_CommandNewTxn'txnTtlSeconds
(\ x__ :: CommandNewTxn
x__ y__ :: Maybe Word64
y__ -> CommandNewTxn
x__ {_CommandNewTxn'txnTtlSeconds :: Maybe Word64
_CommandNewTxn'txnTtlSeconds = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandNewTxn "maybe'txnTtlSeconds" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnTtlSeconds"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn
-> f CommandNewTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn -> f CommandNewTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn
-> f CommandNewTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxn -> Maybe Word64)
-> (CommandNewTxn -> Maybe Word64 -> CommandNewTxn)
-> Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> Maybe Word64
_CommandNewTxn'txnTtlSeconds
(\ x__ :: CommandNewTxn
x__ y__ :: Maybe Word64
y__ -> CommandNewTxn
x__ {_CommandNewTxn'txnTtlSeconds :: Maybe Word64
_CommandNewTxn'txnTtlSeconds = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxn "tcId" Data.Word.Word64 where
fieldOf :: Proxy# "tcId"
-> (Word64 -> f Word64) -> CommandNewTxn -> f CommandNewTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn -> f CommandNewTxn)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandNewTxn
-> f CommandNewTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxn -> Maybe Word64)
-> (CommandNewTxn -> Maybe Word64 -> CommandNewTxn)
-> Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> Maybe Word64
_CommandNewTxn'tcId (\ x__ :: CommandNewTxn
x__ y__ :: Maybe Word64
y__ -> CommandNewTxn
x__ {_CommandNewTxn'tcId :: Maybe Word64
_CommandNewTxn'tcId = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandNewTxn "maybe'tcId" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'tcId"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn
-> f CommandNewTxn
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn -> f CommandNewTxn)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxn
-> f CommandNewTxn
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxn -> Maybe Word64)
-> (CommandNewTxn -> Maybe Word64 -> CommandNewTxn)
-> Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> Maybe Word64
_CommandNewTxn'tcId (\ x__ :: CommandNewTxn
x__ y__ :: Maybe Word64
y__ -> CommandNewTxn
x__ {_CommandNewTxn'tcId :: Maybe Word64
_CommandNewTxn'tcId = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandNewTxn where
messageName :: Proxy CommandNewTxn -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandNewTxn"
packedMessageDescriptor :: Proxy CommandNewTxn -> ByteString
packedMessageDescriptor _
= "\n\
\\rCommandNewTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2)\n\
\\SItxn_ttl_seconds\CAN\STX \SOH(\EOT:\SOH0R\rtxnTtlSeconds\DC2\SYN\n\
\\ENQtc_id\CAN\ETX \SOH(\EOT:\SOH0R\EOTtcId"
packedFileDescriptor :: Proxy CommandNewTxn -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandNewTxn)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandNewTxn
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxn Word64
-> FieldDescriptor CommandNewTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandNewTxn CommandNewTxn Word64 Word64
-> FieldAccessor CommandNewTxn Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxn
txnTtlSeconds__field_descriptor :: FieldDescriptor CommandNewTxn
txnTtlSeconds__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxn Word64
-> FieldDescriptor CommandNewTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txn_ttl_seconds"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandNewTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnTtlSeconds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnTtlSeconds")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxn
tcId__field_descriptor :: FieldDescriptor CommandNewTxn
tcId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxn Word64
-> FieldDescriptor CommandNewTxn
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"tc_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandNewTxn CommandNewTxn (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandNewTxn Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'tcId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'tcId")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxn
in
[(Tag, FieldDescriptor CommandNewTxn)]
-> Map Tag (FieldDescriptor CommandNewTxn)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandNewTxn
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandNewTxn
txnTtlSeconds__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandNewTxn
tcId__field_descriptor)]
unknownFields :: LensLike' f CommandNewTxn FieldSet
unknownFields
= (CommandNewTxn -> FieldSet)
-> (CommandNewTxn -> FieldSet -> CommandNewTxn)
-> Lens' CommandNewTxn FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxn -> FieldSet
_CommandNewTxn'_unknownFields
(\ x__ :: CommandNewTxn
x__ y__ :: FieldSet
y__ -> CommandNewTxn
x__ {_CommandNewTxn'_unknownFields :: FieldSet
_CommandNewTxn'_unknownFields = FieldSet
y__})
defMessage :: CommandNewTxn
defMessage
= $WCommandNewTxn'_constructor :: Word64 -> Maybe Word64 -> Maybe Word64 -> FieldSet -> CommandNewTxn
CommandNewTxn'_constructor
{_CommandNewTxn'requestId :: Word64
_CommandNewTxn'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandNewTxn'txnTtlSeconds :: Maybe Word64
_CommandNewTxn'txnTtlSeconds = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxn'tcId :: Maybe Word64
_CommandNewTxn'tcId = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxn'_unknownFields :: FieldSet
_CommandNewTxn'_unknownFields = []}
parseMessage :: Parser CommandNewTxn
parseMessage
= let
loop ::
CommandNewTxn
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandNewTxn
loop :: CommandNewTxn -> Bool -> Parser CommandNewTxn
loop x :: CommandNewTxn
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandNewTxn -> Parser CommandNewTxn
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandNewTxn CommandNewTxn FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandNewTxn -> CommandNewTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandNewTxn CommandNewTxn FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandNewTxn
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandNewTxn -> Bool -> Parser CommandNewTxn
loop
(Setter CommandNewTxn CommandNewTxn Word64 Word64
-> Word64 -> CommandNewTxn -> CommandNewTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandNewTxn
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txn_ttl_seconds"
CommandNewTxn -> Bool -> Parser CommandNewTxn
loop
(Setter CommandNewTxn CommandNewTxn Word64 Word64
-> Word64 -> CommandNewTxn -> CommandNewTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnTtlSeconds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnTtlSeconds") Word64
y CommandNewTxn
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "tc_id"
CommandNewTxn -> Bool -> Parser CommandNewTxn
loop
(Setter CommandNewTxn CommandNewTxn Word64 Word64
-> Word64 -> CommandNewTxn -> CommandNewTxn
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "tcId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"tcId") Word64
y CommandNewTxn
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandNewTxn -> Bool -> Parser CommandNewTxn
loop
(Setter CommandNewTxn CommandNewTxn FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandNewTxn -> CommandNewTxn
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandNewTxn CommandNewTxn FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandNewTxn
x)
Bool
required'requestId
in
Parser CommandNewTxn -> String -> Parser CommandNewTxn
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandNewTxn -> Bool -> Parser CommandNewTxn
loop CommandNewTxn
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "CommandNewTxn"
buildMessage :: CommandNewTxn -> Builder
buildMessage
= \ _x :: CommandNewTxn
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandNewTxn CommandNewTxn Word64 Word64
-> CommandNewTxn -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandNewTxn
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandNewTxn
CommandNewTxn
(Maybe Word64)
(Maybe Word64)
-> CommandNewTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnTtlSeconds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnTtlSeconds") CommandNewTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandNewTxn
CommandNewTxn
(Maybe Word64)
(Maybe Word64)
-> CommandNewTxn -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'tcId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'tcId") CommandNewTxn
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandNewTxn CommandNewTxn FieldSet FieldSet
-> CommandNewTxn -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandNewTxn CommandNewTxn FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandNewTxn
_x))))
instance Control.DeepSeq.NFData CommandNewTxn where
rnf :: CommandNewTxn -> ()
rnf
= \ x__ :: CommandNewTxn
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxn -> FieldSet
_CommandNewTxn'_unknownFields CommandNewTxn
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxn -> Word64
_CommandNewTxn'requestId CommandNewTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxn -> Maybe Word64
_CommandNewTxn'txnTtlSeconds CommandNewTxn
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandNewTxn -> Maybe Word64
_CommandNewTxn'tcId CommandNewTxn
x__) ())))
data CommandNewTxnResponse
= CommandNewTxnResponse'_constructor {CommandNewTxnResponse -> Word64
_CommandNewTxnResponse'requestId :: !Data.Word.Word64,
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandNewTxnResponse -> Maybe ServerError
_CommandNewTxnResponse'error :: !(Prelude.Maybe ServerError),
CommandNewTxnResponse -> Maybe Text
_CommandNewTxnResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandNewTxnResponse -> FieldSet
_CommandNewTxnResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
(CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> Eq CommandNewTxnResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c/= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
== :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c== :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
Prelude.Eq, Eq CommandNewTxnResponse
Eq CommandNewTxnResponse =>
(CommandNewTxnResponse -> CommandNewTxnResponse -> Ordering)
-> (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> (CommandNewTxnResponse -> CommandNewTxnResponse -> Bool)
-> (CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse)
-> (CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse)
-> Ord CommandNewTxnResponse
CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
CommandNewTxnResponse -> CommandNewTxnResponse -> Ordering
CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse
$cmin :: CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse
max :: CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse
$cmax :: CommandNewTxnResponse
-> CommandNewTxnResponse -> CommandNewTxnResponse
>= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c>= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
> :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c> :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
<= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c<= :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
< :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
$c< :: CommandNewTxnResponse -> CommandNewTxnResponse -> Bool
compare :: CommandNewTxnResponse -> CommandNewTxnResponse -> Ordering
$ccompare :: CommandNewTxnResponse -> CommandNewTxnResponse -> Ordering
$cp1Ord :: Eq CommandNewTxnResponse
Prelude.Ord)
instance Prelude.Show CommandNewTxnResponse where
showsPrec :: Int -> CommandNewTxnResponse -> ShowS
showsPrec _ __x :: CommandNewTxnResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandNewTxnResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandNewTxnResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Word64)
-> (CommandNewTxnResponse -> Word64 -> CommandNewTxnResponse)
-> Lens CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Word64
_CommandNewTxnResponse'requestId
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Word64
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'requestId :: Word64
_CommandNewTxnResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Word64)
-> (CommandNewTxnResponse -> Maybe Word64 -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidLeastBits
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'txnidLeastBits :: Maybe Word64
_CommandNewTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Word64)
-> (CommandNewTxnResponse -> Maybe Word64 -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidLeastBits
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'txnidLeastBits :: Maybe Word64
_CommandNewTxnResponse'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Word64)
-> (CommandNewTxnResponse -> Maybe Word64 -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidMostBits
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'txnidMostBits :: Maybe Word64
_CommandNewTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Word64)
-> (CommandNewTxnResponse -> Maybe Word64 -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidMostBits
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Word64
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'txnidMostBits :: Maybe Word64
_CommandNewTxnResponse'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe ServerError)
-> (CommandNewTxnResponse
-> Maybe ServerError -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe ServerError
_CommandNewTxnResponse'error
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'error :: Maybe ServerError
_CommandNewTxnResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe ServerError)
-> (CommandNewTxnResponse
-> Maybe ServerError -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe ServerError
_CommandNewTxnResponse'error
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe ServerError
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'error :: Maybe ServerError
_CommandNewTxnResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Text)
-> (CommandNewTxnResponse -> Maybe Text -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Text
_CommandNewTxnResponse'message
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Text
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'message :: Maybe Text
_CommandNewTxnResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandNewTxnResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandNewTxnResponse -> f CommandNewTxnResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandNewTxnResponse
-> f CommandNewTxnResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandNewTxnResponse -> Maybe Text)
-> (CommandNewTxnResponse -> Maybe Text -> CommandNewTxnResponse)
-> Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> Maybe Text
_CommandNewTxnResponse'message
(\ x__ :: CommandNewTxnResponse
x__ y__ :: Maybe Text
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'message :: Maybe Text
_CommandNewTxnResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandNewTxnResponse where
messageName :: Proxy CommandNewTxnResponse -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandNewTxnResponse"
packedMessageDescriptor :: Proxy CommandNewTxnResponse -> ByteString
packedMessageDescriptor _
= "\n\
\\NAKCommandNewTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage"
packedFileDescriptor :: Proxy CommandNewTxnResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandNewTxnResponse)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandNewTxnResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxnResponse Word64
-> FieldDescriptor CommandNewTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
-> FieldAccessor CommandNewTxnResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxnResponse
txnidLeastBits__field_descriptor :: FieldDescriptor CommandNewTxnResponse
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxnResponse Word64
-> FieldDescriptor CommandNewTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandNewTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxnResponse
txnidMostBits__field_descriptor :: FieldDescriptor CommandNewTxnResponse
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandNewTxnResponse Word64
-> FieldDescriptor CommandNewTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor CommandNewTxnResponse Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxnResponse
error__field_descriptor :: FieldDescriptor CommandNewTxnResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandNewTxnResponse ServerError
-> FieldDescriptor CommandNewTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor CommandNewTxnResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxnResponse
message__field_descriptor :: FieldDescriptor CommandNewTxnResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandNewTxnResponse Text
-> FieldDescriptor CommandNewTxnResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandNewTxnResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandNewTxnResponse
in
[(Tag, FieldDescriptor CommandNewTxnResponse)]
-> Map Tag (FieldDescriptor CommandNewTxnResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandNewTxnResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandNewTxnResponse
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandNewTxnResponse
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandNewTxnResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandNewTxnResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandNewTxnResponse FieldSet
unknownFields
= (CommandNewTxnResponse -> FieldSet)
-> (CommandNewTxnResponse -> FieldSet -> CommandNewTxnResponse)
-> Lens' CommandNewTxnResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandNewTxnResponse -> FieldSet
_CommandNewTxnResponse'_unknownFields
(\ x__ :: CommandNewTxnResponse
x__ y__ :: FieldSet
y__ -> CommandNewTxnResponse
x__ {_CommandNewTxnResponse'_unknownFields :: FieldSet
_CommandNewTxnResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandNewTxnResponse
defMessage
= $WCommandNewTxnResponse'_constructor :: Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandNewTxnResponse
CommandNewTxnResponse'_constructor
{_CommandNewTxnResponse'requestId :: Word64
_CommandNewTxnResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandNewTxnResponse'txnidLeastBits :: Maybe Word64
_CommandNewTxnResponse'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxnResponse'txnidMostBits :: Maybe Word64
_CommandNewTxnResponse'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxnResponse'error :: Maybe ServerError
_CommandNewTxnResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxnResponse'message :: Maybe Text
_CommandNewTxnResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandNewTxnResponse'_unknownFields :: FieldSet
_CommandNewTxnResponse'_unknownFields = []}
parseMessage :: Parser CommandNewTxnResponse
parseMessage
= let
loop ::
CommandNewTxnResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandNewTxnResponse
loop :: CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop x :: CommandNewTxnResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandNewTxnResponse -> Parser CommandNewTxnResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandNewTxnResponse CommandNewTxnResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandNewTxnResponse
-> CommandNewTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandNewTxnResponse CommandNewTxnResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandNewTxnResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
-> Word64 -> CommandNewTxnResponse -> CommandNewTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandNewTxnResponse
x)
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
-> Word64 -> CommandNewTxnResponse -> CommandNewTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandNewTxnResponse
x)
Bool
required'requestId
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
-> Word64 -> CommandNewTxnResponse -> CommandNewTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandNewTxnResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter
CommandNewTxnResponse CommandNewTxnResponse ServerError ServerError
-> ServerError -> CommandNewTxnResponse -> CommandNewTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandNewTxnResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter CommandNewTxnResponse CommandNewTxnResponse Text Text
-> Text -> CommandNewTxnResponse -> CommandNewTxnResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandNewTxnResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop
(Setter
CommandNewTxnResponse CommandNewTxnResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandNewTxnResponse
-> CommandNewTxnResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandNewTxnResponse CommandNewTxnResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandNewTxnResponse
x)
Bool
required'requestId
in
Parser CommandNewTxnResponse
-> String -> Parser CommandNewTxnResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandNewTxnResponse -> Bool -> Parser CommandNewTxnResponse
loop CommandNewTxnResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandNewTxnResponse"
buildMessage :: CommandNewTxnResponse -> Builder
buildMessage
= \ _x :: CommandNewTxnResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandNewTxnResponse CommandNewTxnResponse Word64 Word64
-> CommandNewTxnResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandNewTxnResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandNewTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandNewTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Word64)
(Maybe Word64)
-> CommandNewTxnResponse -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandNewTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandNewTxnResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandNewTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandNewTxnResponse
CommandNewTxnResponse
(Maybe Text)
(Maybe Text)
-> CommandNewTxnResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandNewTxnResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandNewTxnResponse
CommandNewTxnResponse
FieldSet
FieldSet
-> CommandNewTxnResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandNewTxnResponse
CommandNewTxnResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandNewTxnResponse
_x))))))
instance Control.DeepSeq.NFData CommandNewTxnResponse where
rnf :: CommandNewTxnResponse -> ()
rnf
= \ x__ :: CommandNewTxnResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> FieldSet
_CommandNewTxnResponse'_unknownFields CommandNewTxnResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> Word64
_CommandNewTxnResponse'requestId CommandNewTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidLeastBits CommandNewTxnResponse
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> Maybe Word64
_CommandNewTxnResponse'txnidMostBits CommandNewTxnResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> Maybe ServerError
_CommandNewTxnResponse'error CommandNewTxnResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandNewTxnResponse -> Maybe Text
_CommandNewTxnResponse'message CommandNewTxnResponse
x__) ())))))
data CommandPartitionedTopicMetadata
= CommandPartitionedTopicMetadata'_constructor {CommandPartitionedTopicMetadata -> Text
_CommandPartitionedTopicMetadata'topic :: !Data.Text.Text,
CommandPartitionedTopicMetadata -> Word64
_CommandPartitionedTopicMetadata'requestId :: !Data.Word.Word64,
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal :: !(Prelude.Maybe Data.Text.Text),
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData :: !(Prelude.Maybe Data.Text.Text),
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod :: !(Prelude.Maybe Data.Text.Text),
CommandPartitionedTopicMetadata -> FieldSet
_CommandPartitionedTopicMetadata'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
(CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> Eq CommandPartitionedTopicMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c/= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
== :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c== :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
Prelude.Eq, Eq CommandPartitionedTopicMetadata
Eq CommandPartitionedTopicMetadata =>
(CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Ordering)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata)
-> (CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata)
-> Ord CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Ordering
CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
$cmin :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
max :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
$cmax :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
>= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c>= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
> :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c> :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
<= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c<= :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
< :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
$c< :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Bool
compare :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Ordering
$ccompare :: CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata -> Ordering
$cp1Ord :: Eq CommandPartitionedTopicMetadata
Prelude.Ord)
instance Prelude.Show CommandPartitionedTopicMetadata where
showsPrec :: Int -> CommandPartitionedTopicMetadata -> ShowS
showsPrec _ __x :: CommandPartitionedTopicMetadata
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandPartitionedTopicMetadata -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandPartitionedTopicMetadata
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Text)
-> (CommandPartitionedTopicMetadata
-> Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Text
_CommandPartitionedTopicMetadata'topic
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Text
y__ -> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'topic :: Text
_CommandPartitionedTopicMetadata'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Word64 -> f Word64)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Word64)
-> (CommandPartitionedTopicMetadata
-> Word64 -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Word64
_CommandPartitionedTopicMetadata'requestId
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Word64
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'requestId :: Word64
_CommandPartitionedTopicMetadata'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "originalPrincipal" Data.Text.Text where
fieldOf :: Proxy# "originalPrincipal"
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'originalPrincipal :: Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "maybe'originalPrincipal" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalPrincipal"
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'originalPrincipal :: Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "originalAuthData" Data.Text.Text where
fieldOf :: Proxy# "originalAuthData"
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'originalAuthData :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "maybe'originalAuthData" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthData"
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'originalAuthData :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "originalAuthMethod" Data.Text.Text where
fieldOf :: Proxy# "originalAuthMethod"
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__
{_CommandPartitionedTopicMetadata'originalAuthMethod :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadata "maybe'originalAuthMethod" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'originalAuthMethod"
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadata
-> f CommandPartitionedTopicMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadata -> Maybe Text)
-> (CommandPartitionedTopicMetadata
-> Maybe Text -> CommandPartitionedTopicMetadata)
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadata
x__
{_CommandPartitionedTopicMetadata'originalAuthMethod :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandPartitionedTopicMetadata where
messageName :: Proxy CommandPartitionedTopicMetadata -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandPartitionedTopicMetadata"
packedMessageDescriptor :: Proxy CommandPartitionedTopicMetadata -> ByteString
packedMessageDescriptor _
= "\n\
\\USCommandPartitionedTopicMetadata\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2-\n\
\\DC2original_principal\CAN\ETX \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\EOT \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\ENQ \SOH(\tR\DC2originalAuthMethod"
packedFileDescriptor :: Proxy CommandPartitionedTopicMetadata -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandPartitionedTopicMetadata)
fieldsByTag
= let
topic__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadata
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandPartitionedTopicMetadata Text
-> FieldDescriptor CommandPartitionedTopicMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> FieldAccessor CommandPartitionedTopicMetadata Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadata
requestId__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadata
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandPartitionedTopicMetadata Word64
-> FieldDescriptor CommandPartitionedTopicMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Word64
Word64
-> FieldAccessor CommandPartitionedTopicMetadata Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadata
originalPrincipal__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadata
originalPrincipal__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandPartitionedTopicMetadata Text
-> FieldDescriptor CommandPartitionedTopicMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_principal"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandPartitionedTopicMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadata
originalAuthData__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadata
originalAuthData__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandPartitionedTopicMetadata Text
-> FieldDescriptor CommandPartitionedTopicMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_data"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandPartitionedTopicMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadata
originalAuthMethod__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadata
originalAuthMethod__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandPartitionedTopicMetadata Text
-> FieldDescriptor CommandPartitionedTopicMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"original_auth_method"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandPartitionedTopicMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadata
in
[(Tag, FieldDescriptor CommandPartitionedTopicMetadata)]
-> Map Tag (FieldDescriptor CommandPartitionedTopicMetadata)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandPartitionedTopicMetadata
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandPartitionedTopicMetadata
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandPartitionedTopicMetadata
originalPrincipal__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandPartitionedTopicMetadata
originalAuthData__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandPartitionedTopicMetadata
originalAuthMethod__field_descriptor)]
unknownFields :: LensLike' f CommandPartitionedTopicMetadata FieldSet
unknownFields
= (CommandPartitionedTopicMetadata -> FieldSet)
-> (CommandPartitionedTopicMetadata
-> FieldSet -> CommandPartitionedTopicMetadata)
-> Lens' CommandPartitionedTopicMetadata FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadata -> FieldSet
_CommandPartitionedTopicMetadata'_unknownFields
(\ x__ :: CommandPartitionedTopicMetadata
x__ y__ :: FieldSet
y__
-> CommandPartitionedTopicMetadata
x__ {_CommandPartitionedTopicMetadata'_unknownFields :: FieldSet
_CommandPartitionedTopicMetadata'_unknownFields = FieldSet
y__})
defMessage :: CommandPartitionedTopicMetadata
defMessage
= $WCommandPartitionedTopicMetadata'_constructor :: Text
-> Word64
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> FieldSet
-> CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata'_constructor
{_CommandPartitionedTopicMetadata'topic :: Text
_CommandPartitionedTopicMetadata'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandPartitionedTopicMetadata'requestId :: Word64
_CommandPartitionedTopicMetadata'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandPartitionedTopicMetadata'originalPrincipal :: Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadata'originalAuthData :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadata'originalAuthMethod :: Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadata'_unknownFields :: FieldSet
_CommandPartitionedTopicMetadata'_unknownFields = []}
parseMessage :: Parser CommandPartitionedTopicMetadata
parseMessage
= let
loop ::
CommandPartitionedTopicMetadata
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandPartitionedTopicMetadata
loop :: CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop x :: CommandPartitionedTopicMetadata
x required'requestId :: Bool
required'requestId required'topic :: Bool
required'topic
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandPartitionedTopicMetadata
-> Parser CommandPartitionedTopicMetadata
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandPartitionedTopicMetadata
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> Text
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandPartitionedTopicMetadata
x)
Bool
required'requestId
Bool
Prelude.False
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Word64
Word64
-> Word64
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandPartitionedTopicMetadata
x)
Bool
Prelude.False
Bool
required'topic
26
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_principal"
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> Text
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalPrincipal") Text
y CommandPartitionedTopicMetadata
x)
Bool
required'requestId
Bool
required'topic
34
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_data"
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> Text
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthData") Text
y CommandPartitionedTopicMetadata
x)
Bool
required'requestId
Bool
required'topic
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"original_auth_method"
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> Text
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"originalAuthMethod") Text
y CommandPartitionedTopicMetadata
x)
Bool
required'requestId
Bool
required'topic
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop
(Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandPartitionedTopicMetadata
-> CommandPartitionedTopicMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandPartitionedTopicMetadata
x)
Bool
required'requestId
Bool
required'topic
in
Parser CommandPartitionedTopicMetadata
-> String -> Parser CommandPartitionedTopicMetadata
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandPartitionedTopicMetadata
-> Bool -> Bool -> Parser CommandPartitionedTopicMetadata
loop CommandPartitionedTopicMetadata
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandPartitionedTopicMetadata"
buildMessage :: CommandPartitionedTopicMetadata -> Builder
buildMessage
= \ _x :: CommandPartitionedTopicMetadata
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike
Text
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Text
Text
-> CommandPartitionedTopicMetadata -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandPartitionedTopicMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
Word64
Word64
-> CommandPartitionedTopicMetadata -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandPartitionedTopicMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> CommandPartitionedTopicMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalPrincipal" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalPrincipal") CommandPartitionedTopicMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> CommandPartitionedTopicMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthData") CommandPartitionedTopicMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
(Maybe Text)
(Maybe Text)
-> CommandPartitionedTopicMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'originalAuthMethod" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'originalAuthMethod") CommandPartitionedTopicMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
-> CommandPartitionedTopicMetadata -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandPartitionedTopicMetadata
CommandPartitionedTopicMetadata
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandPartitionedTopicMetadata
_x))))))
instance Control.DeepSeq.NFData CommandPartitionedTopicMetadata where
rnf :: CommandPartitionedTopicMetadata -> ()
rnf
= \ x__ :: CommandPartitionedTopicMetadata
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> FieldSet
_CommandPartitionedTopicMetadata'_unknownFields CommandPartitionedTopicMetadata
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> Text
_CommandPartitionedTopicMetadata'topic CommandPartitionedTopicMetadata
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> Word64
_CommandPartitionedTopicMetadata'requestId CommandPartitionedTopicMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalPrincipal CommandPartitionedTopicMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthData CommandPartitionedTopicMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadata -> Maybe Text
_CommandPartitionedTopicMetadata'originalAuthMethod CommandPartitionedTopicMetadata
x__) ())))))
data CommandPartitionedTopicMetadataResponse
= CommandPartitionedTopicMetadataResponse'_constructor {CommandPartitionedTopicMetadataResponse -> Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions :: !(Prelude.Maybe Data.Word.Word32),
CommandPartitionedTopicMetadataResponse -> Word64
_CommandPartitionedTopicMetadataResponse'requestId :: !Data.Word.Word64,
CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response :: !(Prelude.Maybe CommandPartitionedTopicMetadataResponse'LookupType),
CommandPartitionedTopicMetadataResponse -> Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error :: !(Prelude.Maybe ServerError),
CommandPartitionedTopicMetadataResponse -> Maybe Text
_CommandPartitionedTopicMetadataResponse'message :: !(Prelude.Maybe Data.Text.Text),
CommandPartitionedTopicMetadataResponse -> FieldSet
_CommandPartitionedTopicMetadataResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
(CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> Eq CommandPartitionedTopicMetadataResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c/= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
== :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c== :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
Prelude.Eq, Eq CommandPartitionedTopicMetadataResponse
Eq CommandPartitionedTopicMetadataResponse =>
(CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Ordering)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse)
-> (CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse)
-> Ord CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Ordering
CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
$cmin :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
max :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
$cmax :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
>= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c>= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
> :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c> :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
<= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c<= :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
< :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
$c< :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Bool
compare :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Ordering
$ccompare :: CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse -> Ordering
$cp1Ord :: Eq CommandPartitionedTopicMetadataResponse
Prelude.Ord)
instance Prelude.Show CommandPartitionedTopicMetadataResponse where
showsPrec :: Int -> CommandPartitionedTopicMetadataResponse -> ShowS
showsPrec _ __x :: CommandPartitionedTopicMetadataResponse
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandPartitionedTopicMetadataResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandPartitionedTopicMetadataResponse
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "partitions" Data.Word.Word32 where
fieldOf :: Proxy# "partitions"
-> (Word32 -> f Word32)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Word32 -> f Word32) -> Maybe Word32 -> f (Maybe Word32))
-> (Word32 -> f Word32)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe Word32)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe Word32 -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Word32)
(Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe Word32
y__
-> CommandPartitionedTopicMetadataResponse
x__
{_CommandPartitionedTopicMetadataResponse'partitions :: Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions = Maybe Word32
y__}))
(Word32 -> Lens' (Maybe Word32) Word32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "maybe'partitions" (Prelude.Maybe Data.Word.Word32) where
fieldOf :: Proxy# "maybe'partitions"
-> (Maybe Word32 -> f (Maybe Word32))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32))
-> (Maybe Word32 -> f (Maybe Word32))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe Word32)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe Word32 -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Word32)
(Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe Word32
y__
-> CommandPartitionedTopicMetadataResponse
x__
{_CommandPartitionedTopicMetadataResponse'partitions :: Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions = Maybe Word32
y__}))
(Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Word64 -> f Word64)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Word64)
-> (CommandPartitionedTopicMetadataResponse
-> Word64 -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Word64
_CommandPartitionedTopicMetadataResponse'requestId
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Word64
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'requestId :: Word64
_CommandPartitionedTopicMetadataResponse'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "response" CommandPartitionedTopicMetadataResponse'LookupType where
fieldOf :: Proxy# "response"
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> f CommandPartitionedTopicMetadataResponse'LookupType)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((CommandPartitionedTopicMetadataResponse'LookupType
-> f CommandPartitionedTopicMetadataResponse'LookupType)
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> f CommandPartitionedTopicMetadataResponse'LookupType)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe CommandPartitionedTopicMetadataResponse'LookupType
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'response :: Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response = Maybe CommandPartitionedTopicMetadataResponse'LookupType
y__}))
(CommandPartitionedTopicMetadataResponse'LookupType
-> Lens'
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
CommandPartitionedTopicMetadataResponse'LookupType
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandPartitionedTopicMetadataResponse'LookupType
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "maybe'response" (Prelude.Maybe CommandPartitionedTopicMetadataResponse'LookupType) where
fieldOf :: Proxy# "maybe'response"
-> (Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> (Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe CommandPartitionedTopicMetadataResponse'LookupType
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'response :: Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response = Maybe CommandPartitionedTopicMetadataResponse'LookupType
y__}))
(Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType))
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> f (Maybe CommandPartitionedTopicMetadataResponse'LookupType)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((ServerError -> f ServerError)
-> Maybe ServerError -> f (Maybe ServerError))
-> (ServerError -> f ServerError)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe ServerError)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe ServerError -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe ServerError
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'error :: Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error = Maybe ServerError
y__}))
(ServerError -> Lens' (Maybe ServerError) ServerError
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "maybe'error" (Prelude.Maybe ServerError) where
fieldOf :: Proxy# "maybe'error"
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe ServerError -> f (Maybe ServerError))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError))
-> (Maybe ServerError -> f (Maybe ServerError))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe ServerError)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe ServerError -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe ServerError)
(Maybe ServerError)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe ServerError
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'error :: Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error = Maybe ServerError
y__}))
(Maybe ServerError -> f (Maybe ServerError))
-> Maybe ServerError -> f (Maybe ServerError)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe Text)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe Text -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe Text
_CommandPartitionedTopicMetadataResponse'message
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'message :: Maybe Text
_CommandPartitionedTopicMetadataResponse'message = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandPartitionedTopicMetadataResponse "maybe'message" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'message"
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandPartitionedTopicMetadataResponse
-> f CommandPartitionedTopicMetadataResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandPartitionedTopicMetadataResponse -> Maybe Text)
-> (CommandPartitionedTopicMetadataResponse
-> Maybe Text -> CommandPartitionedTopicMetadataResponse)
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> Maybe Text
_CommandPartitionedTopicMetadataResponse'message
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: Maybe Text
y__
-> CommandPartitionedTopicMetadataResponse
x__ {_CommandPartitionedTopicMetadataResponse'message :: Maybe Text
_CommandPartitionedTopicMetadataResponse'message = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandPartitionedTopicMetadataResponse where
messageName :: Proxy CommandPartitionedTopicMetadataResponse -> Text
messageName _
= String -> Text
Data.Text.pack
"pulsar.proto.CommandPartitionedTopicMetadataResponse"
packedMessageDescriptor :: Proxy CommandPartitionedTopicMetadataResponse -> ByteString
packedMessageDescriptor _
= "\n\
\'CommandPartitionedTopicMetadataResponse\DC2\RS\n\
\\n\
\partitions\CAN\SOH \SOH(\rR\n\
\partitions\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2\\\n\
\\bresponse\CAN\ETX \SOH(\SO2@.pulsar.proto.CommandPartitionedTopicMetadataResponse.LookupTypeR\bresponse\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"%\n\
\\n\
\LookupType\DC2\v\n\
\\aSuccess\DLE\NUL\DC2\n\
\\n\
\\ACKFailed\DLE\SOH"
packedFileDescriptor :: Proxy CommandPartitionedTopicMetadataResponse -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandPartitionedTopicMetadataResponse)
fieldsByTag
= let
partitions__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadataResponse
partitions__field_descriptor
= String
-> FieldTypeDescriptor Word32
-> FieldAccessor CommandPartitionedTopicMetadataResponse Word32
-> FieldDescriptor CommandPartitionedTopicMetadataResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partitions"
(ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
(Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Word32)
(Maybe Word32)
-> FieldAccessor CommandPartitionedTopicMetadataResponse Word32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitions")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadataResponse
requestId__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadataResponse
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandPartitionedTopicMetadataResponse Word64
-> FieldDescriptor CommandPartitionedTopicMetadataResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Word64
Word64
-> FieldAccessor CommandPartitionedTopicMetadataResponse Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadataResponse
response__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadataResponse
response__field_descriptor
= String
-> FieldTypeDescriptor
CommandPartitionedTopicMetadataResponse'LookupType
-> FieldAccessor
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse'LookupType
-> FieldDescriptor CommandPartitionedTopicMetadataResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"response"
(ScalarField CommandPartitionedTopicMetadataResponse'LookupType
-> FieldTypeDescriptor
CommandPartitionedTopicMetadataResponse'LookupType
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandPartitionedTopicMetadataResponse'LookupType
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandPartitionedTopicMetadataResponse'LookupType)
(Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
-> FieldAccessor
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse'LookupType
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadataResponse
error__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadataResponse
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor
CommandPartitionedTopicMetadataResponse ServerError
-> FieldDescriptor CommandPartitionedTopicMetadataResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe ServerError)
(Maybe ServerError)
-> FieldAccessor
CommandPartitionedTopicMetadataResponse ServerError
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadataResponse
message__field_descriptor :: FieldDescriptor CommandPartitionedTopicMetadataResponse
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandPartitionedTopicMetadataResponse Text
-> FieldDescriptor CommandPartitionedTopicMetadataResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Text)
(Maybe Text)
-> FieldAccessor CommandPartitionedTopicMetadataResponse Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message")) ::
Data.ProtoLens.FieldDescriptor CommandPartitionedTopicMetadataResponse
in
[(Tag, FieldDescriptor CommandPartitionedTopicMetadataResponse)]
-> Map
Tag (FieldDescriptor CommandPartitionedTopicMetadataResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandPartitionedTopicMetadataResponse
partitions__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandPartitionedTopicMetadataResponse
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandPartitionedTopicMetadataResponse
response__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandPartitionedTopicMetadataResponse
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandPartitionedTopicMetadataResponse
message__field_descriptor)]
unknownFields :: LensLike' f CommandPartitionedTopicMetadataResponse FieldSet
unknownFields
= (CommandPartitionedTopicMetadataResponse -> FieldSet)
-> (CommandPartitionedTopicMetadataResponse
-> FieldSet -> CommandPartitionedTopicMetadataResponse)
-> Lens' CommandPartitionedTopicMetadataResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPartitionedTopicMetadataResponse -> FieldSet
_CommandPartitionedTopicMetadataResponse'_unknownFields
(\ x__ :: CommandPartitionedTopicMetadataResponse
x__ y__ :: FieldSet
y__
-> CommandPartitionedTopicMetadataResponse
x__
{_CommandPartitionedTopicMetadataResponse'_unknownFields :: FieldSet
_CommandPartitionedTopicMetadataResponse'_unknownFields = FieldSet
y__})
defMessage :: CommandPartitionedTopicMetadataResponse
defMessage
= $WCommandPartitionedTopicMetadataResponse'_constructor :: Maybe Word32
-> Word64
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> Maybe ServerError
-> Maybe Text
-> FieldSet
-> CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse'_constructor
{_CommandPartitionedTopicMetadataResponse'partitions :: Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions = Maybe Word32
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadataResponse'requestId :: Word64
_CommandPartitionedTopicMetadataResponse'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandPartitionedTopicMetadataResponse'response :: Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response = Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadataResponse'error :: Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error = Maybe ServerError
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadataResponse'message :: Maybe Text
_CommandPartitionedTopicMetadataResponse'message = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandPartitionedTopicMetadataResponse'_unknownFields :: FieldSet
_CommandPartitionedTopicMetadataResponse'_unknownFields = []}
parseMessage :: Parser CommandPartitionedTopicMetadataResponse
parseMessage
= let
loop ::
CommandPartitionedTopicMetadataResponse
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandPartitionedTopicMetadataResponse
loop :: CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop x :: CommandPartitionedTopicMetadataResponse
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandPartitionedTopicMetadataResponse
-> Parser CommandPartitionedTopicMetadataResponse
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandPartitionedTopicMetadataResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"partitions"
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Word32
Word32
-> Word32
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitions") Word32
y CommandPartitionedTopicMetadataResponse
x)
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Word64
Word64
-> Word64
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandPartitionedTopicMetadataResponse
x)
Bool
Prelude.False
24
-> do CommandPartitionedTopicMetadataResponse'LookupType
y <- Parser CommandPartitionedTopicMetadataResponse'LookupType
-> String
-> Parser CommandPartitionedTopicMetadataResponse'LookupType
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandPartitionedTopicMetadataResponse'LookupType)
-> Parser Int
-> Parser CommandPartitionedTopicMetadataResponse'LookupType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandPartitionedTopicMetadataResponse'LookupType
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"response"
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"response") CommandPartitionedTopicMetadataResponse'LookupType
y CommandPartitionedTopicMetadataResponse
x)
Bool
required'requestId
32
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
ServerError
ServerError
-> ServerError
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandPartitionedTopicMetadataResponse
x)
Bool
required'requestId
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Text
Text
-> Text
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandPartitionedTopicMetadataResponse
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop
(Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandPartitionedTopicMetadataResponse
-> CommandPartitionedTopicMetadataResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandPartitionedTopicMetadataResponse
x)
Bool
required'requestId
in
Parser CommandPartitionedTopicMetadataResponse
-> String -> Parser CommandPartitionedTopicMetadataResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandPartitionedTopicMetadataResponse
-> Bool -> Parser CommandPartitionedTopicMetadataResponse
loop CommandPartitionedTopicMetadataResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandPartitionedTopicMetadataResponse"
buildMessage :: CommandPartitionedTopicMetadataResponse -> Builder
buildMessage
= \ _x :: CommandPartitionedTopicMetadataResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word32)
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Word32)
(Maybe Word32)
-> CommandPartitionedTopicMetadataResponse -> Maybe Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitions" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitions") CommandPartitionedTopicMetadataResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
Word64
Word64
-> CommandPartitionedTopicMetadataResponse -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandPartitionedTopicMetadataResponse
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
(Maybe CommandPartitionedTopicMetadataResponse'LookupType)
-> CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'response" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'response") CommandPartitionedTopicMetadataResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandPartitionedTopicMetadataResponse'LookupType
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Int -> Builder)
-> (CommandPartitionedTopicMetadataResponse'LookupType -> Int)
-> CommandPartitionedTopicMetadataResponse'LookupType
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandPartitionedTopicMetadataResponse'LookupType -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CommandPartitionedTopicMetadataResponse'LookupType
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ServerError)
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe ServerError)
(Maybe ServerError)
-> CommandPartitionedTopicMetadataResponse -> Maybe ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'error") CommandPartitionedTopicMetadataResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ServerError
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
ServerError
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
(Maybe Text)
(Maybe Text)
-> CommandPartitionedTopicMetadataResponse -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'message") CommandPartitionedTopicMetadataResponse
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
-> CommandPartitionedTopicMetadataResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandPartitionedTopicMetadataResponse
CommandPartitionedTopicMetadataResponse
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandPartitionedTopicMetadataResponse
_x))))))
instance Control.DeepSeq.NFData CommandPartitionedTopicMetadataResponse where
rnf :: CommandPartitionedTopicMetadataResponse -> ()
rnf
= \ x__ :: CommandPartitionedTopicMetadataResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse -> FieldSet
_CommandPartitionedTopicMetadataResponse'_unknownFields CommandPartitionedTopicMetadataResponse
x__)
(Maybe Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse -> Maybe Word32
_CommandPartitionedTopicMetadataResponse'partitions CommandPartitionedTopicMetadataResponse
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse -> Word64
_CommandPartitionedTopicMetadataResponse'requestId CommandPartitionedTopicMetadataResponse
x__)
(Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
_CommandPartitionedTopicMetadataResponse'response CommandPartitionedTopicMetadataResponse
x__)
(Maybe ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse -> Maybe ServerError
_CommandPartitionedTopicMetadataResponse'error CommandPartitionedTopicMetadataResponse
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandPartitionedTopicMetadataResponse -> Maybe Text
_CommandPartitionedTopicMetadataResponse'message CommandPartitionedTopicMetadataResponse
x__) ())))))
data CommandPartitionedTopicMetadataResponse'LookupType
= CommandPartitionedTopicMetadataResponse'Success |
CommandPartitionedTopicMetadataResponse'Failed
deriving stock (Int -> CommandPartitionedTopicMetadataResponse'LookupType -> ShowS
[CommandPartitionedTopicMetadataResponse'LookupType] -> ShowS
CommandPartitionedTopicMetadataResponse'LookupType -> String
(Int
-> CommandPartitionedTopicMetadataResponse'LookupType -> ShowS)
-> (CommandPartitionedTopicMetadataResponse'LookupType -> String)
-> ([CommandPartitionedTopicMetadataResponse'LookupType] -> ShowS)
-> Show CommandPartitionedTopicMetadataResponse'LookupType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandPartitionedTopicMetadataResponse'LookupType] -> ShowS
$cshowList :: [CommandPartitionedTopicMetadataResponse'LookupType] -> ShowS
show :: CommandPartitionedTopicMetadataResponse'LookupType -> String
$cshow :: CommandPartitionedTopicMetadataResponse'LookupType -> String
showsPrec :: Int -> CommandPartitionedTopicMetadataResponse'LookupType -> ShowS
$cshowsPrec :: Int -> CommandPartitionedTopicMetadataResponse'LookupType -> ShowS
Prelude.Show, CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
(CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> Eq CommandPartitionedTopicMetadataResponse'LookupType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c/= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
== :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c== :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
Prelude.Eq, Eq CommandPartitionedTopicMetadataResponse'LookupType
Eq CommandPartitionedTopicMetadataResponse'LookupType =>
(CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Ordering)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType)
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType)
-> Ord CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Ordering
CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
$cmin :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
max :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
$cmax :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
>= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c>= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
> :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c> :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
<= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c<= :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
< :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
$c< :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Bool
compare :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Ordering
$ccompare :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType -> Ordering
$cp1Ord :: Eq CommandPartitionedTopicMetadataResponse'LookupType
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandPartitionedTopicMetadataResponse'LookupType where
maybeToEnum :: Int -> Maybe CommandPartitionedTopicMetadataResponse'LookupType
maybeToEnum 0
= CommandPartitionedTopicMetadataResponse'LookupType
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Success
maybeToEnum 1
= CommandPartitionedTopicMetadataResponse'LookupType
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Failed
maybeToEnum _ = Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandPartitionedTopicMetadataResponse'LookupType -> String
showEnum CommandPartitionedTopicMetadataResponse'Success
= "Success"
showEnum CommandPartitionedTopicMetadataResponse'Failed = "Failed"
readEnum :: String -> Maybe CommandPartitionedTopicMetadataResponse'LookupType
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Success"
= CommandPartitionedTopicMetadataResponse'LookupType
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Success
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Failed"
= CommandPartitionedTopicMetadataResponse'LookupType
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. a -> Maybe a
Prelude.Just CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Failed
| Bool
Prelude.otherwise
= Maybe Int
-> (Int
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType)
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandPartitionedTopicMetadataResponse'LookupType where
minBound :: CommandPartitionedTopicMetadataResponse'LookupType
minBound = CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Success
maxBound :: CommandPartitionedTopicMetadataResponse'LookupType
maxBound = CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Failed
instance Prelude.Enum CommandPartitionedTopicMetadataResponse'LookupType where
toEnum :: Int -> CommandPartitionedTopicMetadataResponse'LookupType
toEnum k__ :: Int
k__
= CommandPartitionedTopicMetadataResponse'LookupType
-> (CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType)
-> Maybe CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandPartitionedTopicMetadataResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum LookupType: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
forall a. a -> a
Prelude.id
(Int -> Maybe CommandPartitionedTopicMetadataResponse'LookupType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandPartitionedTopicMetadataResponse'LookupType -> Int
fromEnum CommandPartitionedTopicMetadataResponse'Success = 0
fromEnum CommandPartitionedTopicMetadataResponse'Failed = 1
succ :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
succ CommandPartitionedTopicMetadataResponse'Failed
= String -> CommandPartitionedTopicMetadataResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
"CommandPartitionedTopicMetadataResponse'LookupType.succ: bad argument CommandPartitionedTopicMetadataResponse'Failed. This value would be out of bounds."
succ CommandPartitionedTopicMetadataResponse'Success
= CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Failed
pred :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
pred CommandPartitionedTopicMetadataResponse'Success
= String -> CommandPartitionedTopicMetadataResponse'LookupType
forall a. HasCallStack => String -> a
Prelude.error
"CommandPartitionedTopicMetadataResponse'LookupType.pred: bad argument CommandPartitionedTopicMetadataResponse'Success. This value would be out of bounds."
pred CommandPartitionedTopicMetadataResponse'Failed
= CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Success
enumFrom :: CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
enumFrom = CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
enumFromTo = CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
enumFromThen = CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
enumFromThenTo = CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> CommandPartitionedTopicMetadataResponse'LookupType
-> [CommandPartitionedTopicMetadataResponse'LookupType]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandPartitionedTopicMetadataResponse'LookupType where
fieldDefault :: CommandPartitionedTopicMetadataResponse'LookupType
fieldDefault = CommandPartitionedTopicMetadataResponse'LookupType
CommandPartitionedTopicMetadataResponse'Success
instance Control.DeepSeq.NFData CommandPartitionedTopicMetadataResponse'LookupType where
rnf :: CommandPartitionedTopicMetadataResponse'LookupType -> ()
rnf x__ :: CommandPartitionedTopicMetadataResponse'LookupType
x__ = CommandPartitionedTopicMetadataResponse'LookupType -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandPartitionedTopicMetadataResponse'LookupType
x__ ()
data CommandPing
= CommandPing'_constructor {CommandPing -> FieldSet
_CommandPing'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandPing -> CommandPing -> Bool
(CommandPing -> CommandPing -> Bool)
-> (CommandPing -> CommandPing -> Bool) -> Eq CommandPing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPing -> CommandPing -> Bool
$c/= :: CommandPing -> CommandPing -> Bool
== :: CommandPing -> CommandPing -> Bool
$c== :: CommandPing -> CommandPing -> Bool
Prelude.Eq, Eq CommandPing
Eq CommandPing =>
(CommandPing -> CommandPing -> Ordering)
-> (CommandPing -> CommandPing -> Bool)
-> (CommandPing -> CommandPing -> Bool)
-> (CommandPing -> CommandPing -> Bool)
-> (CommandPing -> CommandPing -> Bool)
-> (CommandPing -> CommandPing -> CommandPing)
-> (CommandPing -> CommandPing -> CommandPing)
-> Ord CommandPing
CommandPing -> CommandPing -> Bool
CommandPing -> CommandPing -> Ordering
CommandPing -> CommandPing -> CommandPing
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandPing -> CommandPing -> CommandPing
$cmin :: CommandPing -> CommandPing -> CommandPing
max :: CommandPing -> CommandPing -> CommandPing
$cmax :: CommandPing -> CommandPing -> CommandPing
>= :: CommandPing -> CommandPing -> Bool
$c>= :: CommandPing -> CommandPing -> Bool
> :: CommandPing -> CommandPing -> Bool
$c> :: CommandPing -> CommandPing -> Bool
<= :: CommandPing -> CommandPing -> Bool
$c<= :: CommandPing -> CommandPing -> Bool
< :: CommandPing -> CommandPing -> Bool
$c< :: CommandPing -> CommandPing -> Bool
compare :: CommandPing -> CommandPing -> Ordering
$ccompare :: CommandPing -> CommandPing -> Ordering
$cp1Ord :: Eq CommandPing
Prelude.Ord)
instance Prelude.Show CommandPing where
showsPrec :: Int -> CommandPing -> ShowS
showsPrec _ __x :: CommandPing
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandPing -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandPing
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Message CommandPing where
messageName :: Proxy CommandPing -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandPing"
packedMessageDescriptor :: Proxy CommandPing -> ByteString
packedMessageDescriptor _
= "\n\
\\vCommandPing"
packedFileDescriptor :: Proxy CommandPing -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandPing)
fieldsByTag = let in [(Tag, FieldDescriptor CommandPing)]
-> Map Tag (FieldDescriptor CommandPing)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList []
unknownFields :: LensLike' f CommandPing FieldSet
unknownFields
= (CommandPing -> FieldSet)
-> (CommandPing -> FieldSet -> CommandPing)
-> Lens' CommandPing FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPing -> FieldSet
_CommandPing'_unknownFields
(\ x__ :: CommandPing
x__ y__ :: FieldSet
y__ -> CommandPing
x__ {_CommandPing'_unknownFields :: FieldSet
_CommandPing'_unknownFields = FieldSet
y__})
defMessage :: CommandPing
defMessage
= $WCommandPing'_constructor :: FieldSet -> CommandPing
CommandPing'_constructor {_CommandPing'_unknownFields :: FieldSet
_CommandPing'_unknownFields = []}
parseMessage :: Parser CommandPing
parseMessage
= let
loop ::
CommandPing -> Data.ProtoLens.Encoding.Bytes.Parser CommandPing
loop :: CommandPing -> Parser CommandPing
loop x :: CommandPing
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
CommandPing -> Parser CommandPing
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandPing CommandPing FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandPing -> CommandPing
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandPing CommandPing FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandPing
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of {
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandPing -> Parser CommandPing
loop
(Setter CommandPing CommandPing FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandPing -> CommandPing
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandPing CommandPing FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandPing
x) }
in
Parser CommandPing -> String -> Parser CommandPing
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandPing -> Parser CommandPing
loop CommandPing
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "CommandPing"
buildMessage :: CommandPing -> Builder
buildMessage
= \ _x :: CommandPing
_x
-> FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandPing CommandPing FieldSet FieldSet
-> CommandPing -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandPing CommandPing FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandPing
_x)
instance Control.DeepSeq.NFData CommandPing where
rnf :: CommandPing -> ()
rnf
= \ x__ :: CommandPing
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandPing -> FieldSet
_CommandPing'_unknownFields CommandPing
x__) ()
data CommandPong
= CommandPong'_constructor {CommandPong -> FieldSet
_CommandPong'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandPong -> CommandPong -> Bool
(CommandPong -> CommandPong -> Bool)
-> (CommandPong -> CommandPong -> Bool) -> Eq CommandPong
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPong -> CommandPong -> Bool
$c/= :: CommandPong -> CommandPong -> Bool
== :: CommandPong -> CommandPong -> Bool
$c== :: CommandPong -> CommandPong -> Bool
Prelude.Eq, Eq CommandPong
Eq CommandPong =>
(CommandPong -> CommandPong -> Ordering)
-> (CommandPong -> CommandPong -> Bool)
-> (CommandPong -> CommandPong -> Bool)
-> (CommandPong -> CommandPong -> Bool)
-> (CommandPong -> CommandPong -> Bool)
-> (CommandPong -> CommandPong -> CommandPong)
-> (CommandPong -> CommandPong -> CommandPong)
-> Ord CommandPong
CommandPong -> CommandPong -> Bool
CommandPong -> CommandPong -> Ordering
CommandPong -> CommandPong -> CommandPong
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandPong -> CommandPong -> CommandPong
$cmin :: CommandPong -> CommandPong -> CommandPong
max :: CommandPong -> CommandPong -> CommandPong
$cmax :: CommandPong -> CommandPong -> CommandPong
>= :: CommandPong -> CommandPong -> Bool
$c>= :: CommandPong -> CommandPong -> Bool
> :: CommandPong -> CommandPong -> Bool
$c> :: CommandPong -> CommandPong -> Bool
<= :: CommandPong -> CommandPong -> Bool
$c<= :: CommandPong -> CommandPong -> Bool
< :: CommandPong -> CommandPong -> Bool
$c< :: CommandPong -> CommandPong -> Bool
compare :: CommandPong -> CommandPong -> Ordering
$ccompare :: CommandPong -> CommandPong -> Ordering
$cp1Ord :: Eq CommandPong
Prelude.Ord)
instance Prelude.Show CommandPong where
showsPrec :: Int -> CommandPong -> ShowS
showsPrec _ __x :: CommandPong
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandPong -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandPong
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Message CommandPong where
messageName :: Proxy CommandPong -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandPong"
packedMessageDescriptor :: Proxy CommandPong -> ByteString
packedMessageDescriptor _
= "\n\
\\vCommandPong"
packedFileDescriptor :: Proxy CommandPong -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandPong)
fieldsByTag = let in [(Tag, FieldDescriptor CommandPong)]
-> Map Tag (FieldDescriptor CommandPong)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList []
unknownFields :: LensLike' f CommandPong FieldSet
unknownFields
= (CommandPong -> FieldSet)
-> (CommandPong -> FieldSet -> CommandPong)
-> Lens' CommandPong FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandPong -> FieldSet
_CommandPong'_unknownFields
(\ x__ :: CommandPong
x__ y__ :: FieldSet
y__ -> CommandPong
x__ {_CommandPong'_unknownFields :: FieldSet
_CommandPong'_unknownFields = FieldSet
y__})
defMessage :: CommandPong
defMessage
= $WCommandPong'_constructor :: FieldSet -> CommandPong
CommandPong'_constructor {_CommandPong'_unknownFields :: FieldSet
_CommandPong'_unknownFields = []}
parseMessage :: Parser CommandPong
parseMessage
= let
loop ::
CommandPong -> Data.ProtoLens.Encoding.Bytes.Parser CommandPong
loop :: CommandPong -> Parser CommandPong
loop x :: CommandPong
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
CommandPong -> Parser CommandPong
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandPong CommandPong FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandPong -> CommandPong
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandPong CommandPong FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandPong
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of {
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandPong -> Parser CommandPong
loop
(Setter CommandPong CommandPong FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandPong -> CommandPong
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandPong CommandPong FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandPong
x) }
in
Parser CommandPong -> String -> Parser CommandPong
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandPong -> Parser CommandPong
loop CommandPong
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "CommandPong"
buildMessage :: CommandPong -> Builder
buildMessage
= \ _x :: CommandPong
_x
-> FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandPong CommandPong FieldSet FieldSet
-> CommandPong -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandPong CommandPong FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandPong
_x)
instance Control.DeepSeq.NFData CommandPong where
rnf :: CommandPong -> ()
rnf
= \ x__ :: CommandPong
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandPong -> FieldSet
_CommandPong'_unknownFields CommandPong
x__) ()
data CommandProducer
= CommandProducer'_constructor {CommandProducer -> Text
_CommandProducer'topic :: !Data.Text.Text,
CommandProducer -> Word64
_CommandProducer'producerId :: !Data.Word.Word64,
CommandProducer -> Word64
_CommandProducer'requestId :: !Data.Word.Word64,
CommandProducer -> Maybe Text
_CommandProducer'producerName :: !(Prelude.Maybe Data.Text.Text),
CommandProducer -> Maybe Bool
_CommandProducer'encrypted :: !(Prelude.Maybe Prelude.Bool),
CommandProducer -> Vector KeyValue
_CommandProducer'metadata :: !(Data.Vector.Vector KeyValue),
CommandProducer -> Maybe Schema
_CommandProducer'schema :: !(Prelude.Maybe Schema),
CommandProducer -> Maybe Word64
_CommandProducer'epoch :: !(Prelude.Maybe Data.Word.Word64),
CommandProducer -> Maybe Bool
_CommandProducer'userProvidedProducerName :: !(Prelude.Maybe Prelude.Bool),
CommandProducer -> FieldSet
_CommandProducer'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandProducer -> CommandProducer -> Bool
(CommandProducer -> CommandProducer -> Bool)
-> (CommandProducer -> CommandProducer -> Bool)
-> Eq CommandProducer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandProducer -> CommandProducer -> Bool
$c/= :: CommandProducer -> CommandProducer -> Bool
== :: CommandProducer -> CommandProducer -> Bool
$c== :: CommandProducer -> CommandProducer -> Bool
Prelude.Eq, Eq CommandProducer
Eq CommandProducer =>
(CommandProducer -> CommandProducer -> Ordering)
-> (CommandProducer -> CommandProducer -> Bool)
-> (CommandProducer -> CommandProducer -> Bool)
-> (CommandProducer -> CommandProducer -> Bool)
-> (CommandProducer -> CommandProducer -> Bool)
-> (CommandProducer -> CommandProducer -> CommandProducer)
-> (CommandProducer -> CommandProducer -> CommandProducer)
-> Ord CommandProducer
CommandProducer -> CommandProducer -> Bool
CommandProducer -> CommandProducer -> Ordering
CommandProducer -> CommandProducer -> CommandProducer
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandProducer -> CommandProducer -> CommandProducer
$cmin :: CommandProducer -> CommandProducer -> CommandProducer
max :: CommandProducer -> CommandProducer -> CommandProducer
$cmax :: CommandProducer -> CommandProducer -> CommandProducer
>= :: CommandProducer -> CommandProducer -> Bool
$c>= :: CommandProducer -> CommandProducer -> Bool
> :: CommandProducer -> CommandProducer -> Bool
$c> :: CommandProducer -> CommandProducer -> Bool
<= :: CommandProducer -> CommandProducer -> Bool
$c<= :: CommandProducer -> CommandProducer -> Bool
< :: CommandProducer -> CommandProducer -> Bool
$c< :: CommandProducer -> CommandProducer -> Bool
compare :: CommandProducer -> CommandProducer -> Ordering
$ccompare :: CommandProducer -> CommandProducer -> Ordering
$cp1Ord :: Eq CommandProducer
Prelude.Ord)
instance Prelude.Show CommandProducer where
showsPrec :: Int -> CommandProducer -> ShowS
showsPrec _ __x :: CommandProducer
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandProducer -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandProducer
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandProducer "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Text -> f Text) -> CommandProducer -> f CommandProducer)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Text)
-> (CommandProducer -> Text -> CommandProducer)
-> Lens CommandProducer CommandProducer Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Text
_CommandProducer'topic
(\ x__ :: CommandProducer
x__ y__ :: Text
y__ -> CommandProducer
x__ {_CommandProducer'topic :: Text
_CommandProducer'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "producerId" Data.Word.Word64 where
fieldOf :: Proxy# "producerId"
-> (Word64 -> f Word64) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Word64 -> f Word64) -> CommandProducer -> f CommandProducer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Word64)
-> (CommandProducer -> Word64 -> CommandProducer)
-> Lens CommandProducer CommandProducer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Word64
_CommandProducer'producerId
(\ x__ :: CommandProducer
x__ y__ :: Word64
y__ -> CommandProducer
x__ {_CommandProducer'producerId :: Word64
_CommandProducer'producerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Word64 -> f Word64) -> CommandProducer -> f CommandProducer)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Word64)
-> (CommandProducer -> Word64 -> CommandProducer)
-> Lens CommandProducer CommandProducer Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Word64
_CommandProducer'requestId
(\ x__ :: CommandProducer
x__ y__ :: Word64
y__ -> CommandProducer
x__ {_CommandProducer'requestId :: Word64
_CommandProducer'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "producerName" Data.Text.Text where
fieldOf :: Proxy# "producerName"
-> (Text -> f Text) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandProducer -> f CommandProducer)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Text)
-> (CommandProducer -> Maybe Text -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Text
_CommandProducer'producerName
(\ x__ :: CommandProducer
x__ y__ :: Maybe Text
y__ -> CommandProducer
x__ {_CommandProducer'producerName :: Maybe Text
_CommandProducer'producerName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandProducer "maybe'producerName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'producerName"
-> (Maybe Text -> f (Maybe Text))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandProducer -> f CommandProducer)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Text)
-> (CommandProducer -> Maybe Text -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Text
_CommandProducer'producerName
(\ x__ :: CommandProducer
x__ y__ :: Maybe Text
y__ -> CommandProducer
x__ {_CommandProducer'producerName :: Maybe Text
_CommandProducer'producerName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "encrypted" Prelude.Bool where
fieldOf :: Proxy# "encrypted"
-> (Bool -> f Bool) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandProducer -> f CommandProducer)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Bool)
-> (CommandProducer -> Maybe Bool -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Bool
_CommandProducer'encrypted
(\ x__ :: CommandProducer
x__ y__ :: Maybe Bool
y__ -> CommandProducer
x__ {_CommandProducer'encrypted :: Maybe Bool
_CommandProducer'encrypted = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandProducer "maybe'encrypted" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'encrypted"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandProducer -> f CommandProducer)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Bool)
-> (CommandProducer -> Maybe Bool -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Bool
_CommandProducer'encrypted
(\ x__ :: CommandProducer
x__ y__ :: Maybe Bool
y__ -> CommandProducer
x__ {_CommandProducer'encrypted :: Maybe Bool
_CommandProducer'encrypted = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "metadata" [KeyValue] where
fieldOf :: Proxy# "metadata"
-> ([KeyValue] -> f [KeyValue])
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> CommandProducer -> f CommandProducer)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Vector KeyValue)
-> (CommandProducer -> Vector KeyValue -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Vector KeyValue
_CommandProducer'metadata
(\ x__ :: CommandProducer
x__ y__ :: Vector KeyValue
y__ -> CommandProducer
x__ {_CommandProducer'metadata :: Vector KeyValue
_CommandProducer'metadata = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField CommandProducer "vec'metadata" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'metadata"
-> (Vector KeyValue -> f (Vector KeyValue))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> CommandProducer -> f CommandProducer)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Vector KeyValue)
-> (CommandProducer -> Vector KeyValue -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Vector KeyValue
_CommandProducer'metadata
(\ x__ :: CommandProducer
x__ y__ :: Vector KeyValue
y__ -> CommandProducer
x__ {_CommandProducer'metadata :: Vector KeyValue
_CommandProducer'metadata = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "schema" Schema where
fieldOf :: Proxy# "schema"
-> (Schema -> f Schema) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandProducer -> f CommandProducer)
-> ((Schema -> f Schema) -> Maybe Schema -> f (Maybe Schema))
-> (Schema -> f Schema)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Schema)
-> (CommandProducer -> Maybe Schema -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Schema
_CommandProducer'schema
(\ x__ :: CommandProducer
x__ y__ :: Maybe Schema
y__ -> CommandProducer
x__ {_CommandProducer'schema :: Maybe Schema
_CommandProducer'schema = Maybe Schema
y__}))
(Schema -> Lens' (Maybe Schema) Schema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandProducer "maybe'schema" (Prelude.Maybe Schema) where
fieldOf :: Proxy# "maybe'schema"
-> (Maybe Schema -> f (Maybe Schema))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandProducer -> f CommandProducer)
-> ((Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema))
-> (Maybe Schema -> f (Maybe Schema))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Schema)
-> (CommandProducer -> Maybe Schema -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Schema
_CommandProducer'schema
(\ x__ :: CommandProducer
x__ y__ :: Maybe Schema
y__ -> CommandProducer
x__ {_CommandProducer'schema :: Maybe Schema
_CommandProducer'schema = Maybe Schema
y__}))
(Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "epoch" Data.Word.Word64 where
fieldOf :: Proxy# "epoch"
-> (Word64 -> f Word64) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandProducer -> f CommandProducer)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Word64)
-> (CommandProducer -> Maybe Word64 -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Word64
_CommandProducer'epoch
(\ x__ :: CommandProducer
x__ y__ :: Maybe Word64
y__ -> CommandProducer
x__ {_CommandProducer'epoch :: Maybe Word64
_CommandProducer'epoch = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandProducer "maybe'epoch" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'epoch"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandProducer -> f CommandProducer)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Word64)
-> (CommandProducer -> Maybe Word64 -> CommandProducer)
-> Lens
CommandProducer CommandProducer (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Word64
_CommandProducer'epoch
(\ x__ :: CommandProducer
x__ y__ :: Maybe Word64
y__ -> CommandProducer
x__ {_CommandProducer'epoch :: Maybe Word64
_CommandProducer'epoch = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducer "userProvidedProducerName" Prelude.Bool where
fieldOf :: Proxy# "userProvidedProducerName"
-> (Bool -> f Bool) -> CommandProducer -> f CommandProducer
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandProducer -> f CommandProducer)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Bool)
-> (CommandProducer -> Maybe Bool -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Bool
_CommandProducer'userProvidedProducerName
(\ x__ :: CommandProducer
x__ y__ :: Maybe Bool
y__
-> CommandProducer
x__ {_CommandProducer'userProvidedProducerName :: Maybe Bool
_CommandProducer'userProvidedProducerName = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.True)
instance Data.ProtoLens.Field.HasField CommandProducer "maybe'userProvidedProducerName" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'userProvidedProducerName"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandProducer
-> f CommandProducer
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandProducer -> f CommandProducer)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandProducer
-> f CommandProducer
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducer -> Maybe Bool)
-> (CommandProducer -> Maybe Bool -> CommandProducer)
-> Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> Maybe Bool
_CommandProducer'userProvidedProducerName
(\ x__ :: CommandProducer
x__ y__ :: Maybe Bool
y__
-> CommandProducer
x__ {_CommandProducer'userProvidedProducerName :: Maybe Bool
_CommandProducer'userProvidedProducerName = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandProducer where
messageName :: Proxy CommandProducer -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandProducer"
packedMessageDescriptor :: Proxy CommandProducer -> ByteString
packedMessageDescriptor _
= "\n\
\\SICommandProducer\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\US\n\
\\vproducer_id\CAN\STX \STX(\EOTR\n\
\producerId\DC2\GS\n\
\\n\
\request_id\CAN\ETX \STX(\EOTR\trequestId\DC2#\n\
\\rproducer_name\CAN\EOT \SOH(\tR\fproducerName\DC2#\n\
\\tencrypted\CAN\ENQ \SOH(\b:\ENQfalseR\tencrypted\DC22\n\
\\bmetadata\CAN\ACK \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata\DC2,\n\
\\ACKschema\CAN\a \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2\ETB\n\
\\ENQepoch\CAN\b \SOH(\EOT:\SOH0R\ENQepoch\DC2C\n\
\\ESCuser_provided_producer_name\CAN\t \SOH(\b:\EOTtrueR\CANuserProvidedProducerName"
packedFileDescriptor :: Proxy CommandProducer -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandProducer)
fieldsByTag
= let
topic__field_descriptor :: FieldDescriptor CommandProducer
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandProducer Text
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandProducer CommandProducer Text Text
-> FieldAccessor CommandProducer Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
producerId__field_descriptor :: FieldDescriptor CommandProducer
producerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandProducer Word64
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandProducer CommandProducer Word64 Word64
-> FieldAccessor CommandProducer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
requestId__field_descriptor :: FieldDescriptor CommandProducer
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandProducer Word64
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandProducer CommandProducer Word64 Word64
-> FieldAccessor CommandProducer Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
producerName__field_descriptor :: FieldDescriptor CommandProducer
producerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandProducer Text
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandProducer CommandProducer (Maybe Text) (Maybe Text)
-> FieldAccessor CommandProducer Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'producerName")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
encrypted__field_descriptor :: FieldDescriptor CommandProducer
encrypted__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandProducer Bool
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"encrypted"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandProducer Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'encrypted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'encrypted")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
metadata__field_descriptor :: FieldDescriptor CommandProducer
metadata__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor CommandProducer KeyValue
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"metadata"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing
-> Lens' CommandProducer [KeyValue]
-> FieldAccessor CommandProducer KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"metadata")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
schema__field_descriptor :: FieldDescriptor CommandProducer
schema__field_descriptor
= String
-> FieldTypeDescriptor Schema
-> FieldAccessor CommandProducer Schema
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema"
(MessageOrGroup -> FieldTypeDescriptor Schema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Schema)
(Lens CommandProducer CommandProducer (Maybe Schema) (Maybe Schema)
-> FieldAccessor CommandProducer Schema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
epoch__field_descriptor :: FieldDescriptor CommandProducer
epoch__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandProducer Word64
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"epoch"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandProducer CommandProducer (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandProducer Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'epoch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'epoch")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
userProvidedProducerName__field_descriptor :: FieldDescriptor CommandProducer
userProvidedProducerName__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandProducer Bool
-> FieldDescriptor CommandProducer
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"user_provided_producer_name"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandProducer CommandProducer (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandProducer Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'userProvidedProducerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'userProvidedProducerName")) ::
Data.ProtoLens.FieldDescriptor CommandProducer
in
[(Tag, FieldDescriptor CommandProducer)]
-> Map Tag (FieldDescriptor CommandProducer)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandProducer
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandProducer
producerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandProducer
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandProducer
producerName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandProducer
encrypted__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandProducer
metadata__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandProducer
schema__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor CommandProducer
epoch__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor CommandProducer
userProvidedProducerName__field_descriptor)]
unknownFields :: LensLike' f CommandProducer FieldSet
unknownFields
= (CommandProducer -> FieldSet)
-> (CommandProducer -> FieldSet -> CommandProducer)
-> Lens' CommandProducer FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducer -> FieldSet
_CommandProducer'_unknownFields
(\ x__ :: CommandProducer
x__ y__ :: FieldSet
y__ -> CommandProducer
x__ {_CommandProducer'_unknownFields :: FieldSet
_CommandProducer'_unknownFields = FieldSet
y__})
defMessage :: CommandProducer
defMessage
= $WCommandProducer'_constructor :: Text
-> Word64
-> Word64
-> Maybe Text
-> Maybe Bool
-> Vector KeyValue
-> Maybe Schema
-> Maybe Word64
-> Maybe Bool
-> FieldSet
-> CommandProducer
CommandProducer'_constructor
{_CommandProducer'topic :: Text
_CommandProducer'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandProducer'producerId :: Word64
_CommandProducer'producerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandProducer'requestId :: Word64
_CommandProducer'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandProducer'producerName :: Maybe Text
_CommandProducer'producerName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandProducer'encrypted :: Maybe Bool
_CommandProducer'encrypted = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandProducer'metadata :: Vector KeyValue
_CommandProducer'metadata = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandProducer'schema :: Maybe Schema
_CommandProducer'schema = Maybe Schema
forall a. Maybe a
Prelude.Nothing,
_CommandProducer'epoch :: Maybe Word64
_CommandProducer'epoch = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandProducer'userProvidedProducerName :: Maybe Bool
_CommandProducer'userProvidedProducerName = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandProducer'_unknownFields :: FieldSet
_CommandProducer'_unknownFields = []}
parseMessage :: Parser CommandProducer
parseMessage
= let
loop ::
CommandProducer
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Bytes.Parser CommandProducer
loop :: CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
x :: CommandProducer
x
required'producerId :: Bool
required'producerId
required'requestId :: Bool
required'requestId
required'topic :: Bool
required'topic
mutable'metadata :: Growing Vector RealWorld KeyValue
mutable'metadata
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector KeyValue
frozen'metadata <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata)
(let
missing :: [String]
missing
= (if Bool
required'producerId then (:) "producer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) []))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandProducer -> Parser CommandProducer
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandProducer CommandProducer FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandProducer CommandProducer FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandProducer CommandProducer (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") Vector KeyValue
frozen'metadata CommandProducer
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Text Text
-> Text -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
Prelude.False
Growing Vector RealWorld KeyValue
mutable'metadata
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "producer_id"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Word64 Word64
-> Word64 -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") Word64
y CommandProducer
x)
Bool
Prelude.False
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Word64 Word64
-> Word64 -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandProducer
x)
Bool
required'producerId
Bool
Prelude.False
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
34
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"producer_name"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Text Text
-> Text -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName") Text
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
40
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"encrypted"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Bool Bool
-> Bool -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "encrypted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"encrypted") Bool
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
50
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"metadata"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata KeyValue
y)
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop CommandProducer
x Bool
required'producerId Bool
required'requestId Bool
required'topic Growing Vector RealWorld KeyValue
v
58
-> do Schema
y <- Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Schema -> Parser Schema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Schema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"schema"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Schema Schema
-> Schema -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") Schema
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
64
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "epoch"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Word64 Word64
-> Word64 -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "epoch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"epoch") Word64
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
72
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"user_provided_producer_name"
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer Bool Bool
-> Bool -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "userProvidedProducerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"userProvidedProducerName") Bool
y CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
(Setter CommandProducer CommandProducer FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandProducer -> CommandProducer
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandProducer CommandProducer FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandProducer
x)
Bool
required'producerId
Bool
required'requestId
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
in
Parser CommandProducer -> String -> Parser CommandProducer
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld KeyValue
mutable'metadata <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandProducer
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandProducer
loop
CommandProducer
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld KeyValue
mutable'metadata)
"CommandProducer"
buildMessage :: CommandProducer -> Builder
buildMessage
= \ _x :: CommandProducer
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandProducer CommandProducer Text Text
-> CommandProducer -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandProducer
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandProducer CommandProducer Word64 Word64
-> CommandProducer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") CommandProducer
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandProducer CommandProducer Word64 Word64
-> CommandProducer -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandProducer
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandProducer
CommandProducer
(Maybe Text)
(Maybe Text)
-> CommandProducer -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'producerName") CommandProducer
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandProducer
CommandProducer
(Maybe Bool)
(Maybe Bool)
-> CommandProducer -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'encrypted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'encrypted") CommandProducer
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue)
CommandProducer
CommandProducer
(Vector KeyValue)
(Vector KeyValue)
-> CommandProducer -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") CommandProducer
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Schema)
CommandProducer
CommandProducer
(Maybe Schema)
(Maybe Schema)
-> CommandProducer -> Maybe Schema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema") CommandProducer
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Schema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder)
-> (Schema -> ByteString) -> Schema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Schema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Schema
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandProducer
CommandProducer
(Maybe Word64)
(Maybe Word64)
-> CommandProducer -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'epoch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'epoch") CommandProducer
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandProducer
CommandProducer
(Maybe Bool)
(Maybe Bool)
-> CommandProducer -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'userProvidedProducerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'userProvidedProducerName")
CommandProducer
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 72)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandProducer CommandProducer FieldSet FieldSet
-> CommandProducer -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandProducer CommandProducer FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandProducer
_x))))))))))
instance Control.DeepSeq.NFData CommandProducer where
rnf :: CommandProducer -> ()
rnf
= \ x__ :: CommandProducer
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> FieldSet
_CommandProducer'_unknownFields CommandProducer
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Text
_CommandProducer'topic CommandProducer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Word64
_CommandProducer'producerId CommandProducer
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Word64
_CommandProducer'requestId CommandProducer
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Maybe Text
_CommandProducer'producerName CommandProducer
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Maybe Bool
_CommandProducer'encrypted CommandProducer
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Vector KeyValue
_CommandProducer'metadata CommandProducer
x__)
(Maybe Schema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Maybe Schema
_CommandProducer'schema CommandProducer
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Maybe Word64
_CommandProducer'epoch CommandProducer
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducer -> Maybe Bool
_CommandProducer'userProvidedProducerName CommandProducer
x__) ())))))))))
data CommandProducerSuccess
= CommandProducerSuccess'_constructor {CommandProducerSuccess -> Word64
_CommandProducerSuccess'requestId :: !Data.Word.Word64,
CommandProducerSuccess -> Text
_CommandProducerSuccess'producerName :: !Data.Text.Text,
CommandProducerSuccess -> Maybe Int64
_CommandProducerSuccess'lastSequenceId :: !(Prelude.Maybe Data.Int.Int64),
CommandProducerSuccess -> Maybe ByteString
_CommandProducerSuccess'schemaVersion :: !(Prelude.Maybe Data.ByteString.ByteString),
CommandProducerSuccess -> FieldSet
_CommandProducerSuccess'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandProducerSuccess -> CommandProducerSuccess -> Bool
(CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> (CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> Eq CommandProducerSuccess
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c/= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
== :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c== :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
Prelude.Eq, Eq CommandProducerSuccess
Eq CommandProducerSuccess =>
(CommandProducerSuccess -> CommandProducerSuccess -> Ordering)
-> (CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> (CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> (CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> (CommandProducerSuccess -> CommandProducerSuccess -> Bool)
-> (CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess)
-> (CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess)
-> Ord CommandProducerSuccess
CommandProducerSuccess -> CommandProducerSuccess -> Bool
CommandProducerSuccess -> CommandProducerSuccess -> Ordering
CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess
$cmin :: CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess
max :: CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess
$cmax :: CommandProducerSuccess
-> CommandProducerSuccess -> CommandProducerSuccess
>= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c>= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
> :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c> :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
<= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c<= :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
< :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
$c< :: CommandProducerSuccess -> CommandProducerSuccess -> Bool
compare :: CommandProducerSuccess -> CommandProducerSuccess -> Ordering
$ccompare :: CommandProducerSuccess -> CommandProducerSuccess -> Ordering
$cp1Ord :: Eq CommandProducerSuccess
Prelude.Ord)
instance Prelude.Show CommandProducerSuccess where
showsPrec :: Int -> CommandProducerSuccess -> ShowS
showsPrec _ __x :: CommandProducerSuccess
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandProducerSuccess -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandProducerSuccess
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Word64 -> f Word64)
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Word64)
-> (CommandProducerSuccess -> Word64 -> CommandProducerSuccess)
-> Lens CommandProducerSuccess CommandProducerSuccess Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Word64
_CommandProducerSuccess'requestId
(\ x__ :: CommandProducerSuccess
x__ y__ :: Word64
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'requestId :: Word64
_CommandProducerSuccess'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "producerName" Data.Text.Text where
fieldOf :: Proxy# "producerName"
-> (Text -> f Text)
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Text -> f Text)
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Text)
-> (CommandProducerSuccess -> Text -> CommandProducerSuccess)
-> Lens CommandProducerSuccess CommandProducerSuccess Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Text
_CommandProducerSuccess'producerName
(\ x__ :: CommandProducerSuccess
x__ y__ :: Text
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'producerName :: Text
_CommandProducerSuccess'producerName = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "lastSequenceId" Data.Int.Int64 where
fieldOf :: Proxy# "lastSequenceId"
-> (Int64 -> f Int64)
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Maybe Int64 -> f (Maybe Int64))
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((Int64 -> f Int64) -> Maybe Int64 -> f (Maybe Int64))
-> (Int64 -> f Int64)
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Maybe Int64)
-> (CommandProducerSuccess
-> Maybe Int64 -> CommandProducerSuccess)
-> Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe Int64)
(Maybe Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Maybe Int64
_CommandProducerSuccess'lastSequenceId
(\ x__ :: CommandProducerSuccess
x__ y__ :: Maybe Int64
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'lastSequenceId :: Maybe Int64
_CommandProducerSuccess'lastSequenceId = Maybe Int64
y__}))
(Int64 -> Lens' (Maybe Int64) Int64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens (-1))
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "maybe'lastSequenceId" (Prelude.Maybe Data.Int.Int64) where
fieldOf :: Proxy# "maybe'lastSequenceId"
-> (Maybe Int64 -> f (Maybe Int64))
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Maybe Int64 -> f (Maybe Int64))
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((Maybe Int64 -> f (Maybe Int64))
-> Maybe Int64 -> f (Maybe Int64))
-> (Maybe Int64 -> f (Maybe Int64))
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Maybe Int64)
-> (CommandProducerSuccess
-> Maybe Int64 -> CommandProducerSuccess)
-> Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe Int64)
(Maybe Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Maybe Int64
_CommandProducerSuccess'lastSequenceId
(\ x__ :: CommandProducerSuccess
x__ y__ :: Maybe Int64
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'lastSequenceId :: Maybe Int64
_CommandProducerSuccess'lastSequenceId = Maybe Int64
y__}))
(Maybe Int64 -> f (Maybe Int64)) -> Maybe Int64 -> f (Maybe Int64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "schemaVersion" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaVersion"
-> (ByteString -> f ByteString)
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Maybe ByteString)
-> (CommandProducerSuccess
-> Maybe ByteString -> CommandProducerSuccess)
-> Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Maybe ByteString
_CommandProducerSuccess'schemaVersion
(\ x__ :: CommandProducerSuccess
x__ y__ :: Maybe ByteString
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'schemaVersion :: Maybe ByteString
_CommandProducerSuccess'schemaVersion = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandProducerSuccess "maybe'schemaVersion" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'schemaVersion"
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandProducerSuccess
-> f CommandProducerSuccess
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> CommandProducerSuccess -> f CommandProducerSuccess)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> CommandProducerSuccess
-> f CommandProducerSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandProducerSuccess -> Maybe ByteString)
-> (CommandProducerSuccess
-> Maybe ByteString -> CommandProducerSuccess)
-> Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> Maybe ByteString
_CommandProducerSuccess'schemaVersion
(\ x__ :: CommandProducerSuccess
x__ y__ :: Maybe ByteString
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'schemaVersion :: Maybe ByteString
_CommandProducerSuccess'schemaVersion = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandProducerSuccess where
messageName :: Proxy CommandProducerSuccess -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandProducerSuccess"
packedMessageDescriptor :: Proxy CommandProducerSuccess -> ByteString
packedMessageDescriptor _
= "\n\
\\SYNCommandProducerSuccess\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2#\n\
\\rproducer_name\CAN\STX \STX(\tR\fproducerName\DC2,\n\
\\DLElast_sequence_id\CAN\ETX \SOH(\ETX:\STX-1R\SOlastSequenceId\DC2%\n\
\\SOschema_version\CAN\EOT \SOH(\fR\rschemaVersion"
packedFileDescriptor :: Proxy CommandProducerSuccess -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandProducerSuccess)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandProducerSuccess
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandProducerSuccess Word64
-> FieldDescriptor CommandProducerSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandProducerSuccess CommandProducerSuccess Word64 Word64
-> FieldAccessor CommandProducerSuccess Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandProducerSuccess
producerName__field_descriptor :: FieldDescriptor CommandProducerSuccess
producerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandProducerSuccess Text
-> FieldDescriptor CommandProducerSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandProducerSuccess CommandProducerSuccess Text Text
-> FieldAccessor CommandProducerSuccess Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName")) ::
Data.ProtoLens.FieldDescriptor CommandProducerSuccess
lastSequenceId__field_descriptor :: FieldDescriptor CommandProducerSuccess
lastSequenceId__field_descriptor
= String
-> FieldTypeDescriptor Int64
-> FieldAccessor CommandProducerSuccess Int64
-> FieldDescriptor CommandProducerSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"last_sequence_id"
(ScalarField Int64 -> FieldTypeDescriptor Int64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int64
Data.ProtoLens.Int64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int64)
(Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe Int64)
(Maybe Int64)
-> FieldAccessor CommandProducerSuccess Int64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'lastSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'lastSequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandProducerSuccess
schemaVersion__field_descriptor :: FieldDescriptor CommandProducerSuccess
schemaVersion__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor CommandProducerSuccess ByteString
-> FieldDescriptor CommandProducerSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_version"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
CommandProducerSuccess
CommandProducerSuccess
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor CommandProducerSuccess ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion")) ::
Data.ProtoLens.FieldDescriptor CommandProducerSuccess
in
[(Tag, FieldDescriptor CommandProducerSuccess)]
-> Map Tag (FieldDescriptor CommandProducerSuccess)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandProducerSuccess
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandProducerSuccess
producerName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandProducerSuccess
lastSequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandProducerSuccess
schemaVersion__field_descriptor)]
unknownFields :: LensLike' f CommandProducerSuccess FieldSet
unknownFields
= (CommandProducerSuccess -> FieldSet)
-> (CommandProducerSuccess -> FieldSet -> CommandProducerSuccess)
-> Lens' CommandProducerSuccess FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandProducerSuccess -> FieldSet
_CommandProducerSuccess'_unknownFields
(\ x__ :: CommandProducerSuccess
x__ y__ :: FieldSet
y__ -> CommandProducerSuccess
x__ {_CommandProducerSuccess'_unknownFields :: FieldSet
_CommandProducerSuccess'_unknownFields = FieldSet
y__})
defMessage :: CommandProducerSuccess
defMessage
= $WCommandProducerSuccess'_constructor :: Word64
-> Text
-> Maybe Int64
-> Maybe ByteString
-> FieldSet
-> CommandProducerSuccess
CommandProducerSuccess'_constructor
{_CommandProducerSuccess'requestId :: Word64
_CommandProducerSuccess'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandProducerSuccess'producerName :: Text
_CommandProducerSuccess'producerName = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandProducerSuccess'lastSequenceId :: Maybe Int64
_CommandProducerSuccess'lastSequenceId = Maybe Int64
forall a. Maybe a
Prelude.Nothing,
_CommandProducerSuccess'schemaVersion :: Maybe ByteString
_CommandProducerSuccess'schemaVersion = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_CommandProducerSuccess'_unknownFields :: FieldSet
_CommandProducerSuccess'_unknownFields = []}
parseMessage :: Parser CommandProducerSuccess
parseMessage
= let
loop ::
CommandProducerSuccess
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandProducerSuccess
loop :: CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop x :: CommandProducerSuccess
x required'producerName :: Bool
required'producerName required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'producerName then
(:) "producer_name"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandProducerSuccess -> Parser CommandProducerSuccess
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandProducerSuccess CommandProducerSuccess FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandProducerSuccess
-> CommandProducerSuccess
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandProducerSuccess CommandProducerSuccess FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandProducerSuccess
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop
(Setter CommandProducerSuccess CommandProducerSuccess Word64 Word64
-> Word64 -> CommandProducerSuccess -> CommandProducerSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandProducerSuccess
x)
Bool
required'producerName
Bool
Prelude.False
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"producer_name"
CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop
(Setter CommandProducerSuccess CommandProducerSuccess Text Text
-> Text -> CommandProducerSuccess -> CommandProducerSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName") Text
y CommandProducerSuccess
x)
Bool
Prelude.False
Bool
required'requestId
24
-> do Int64
y <- Parser Int64 -> String -> Parser Int64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int64) -> Parser Word64 -> Parser Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"last_sequence_id"
CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop
(Setter CommandProducerSuccess CommandProducerSuccess Int64 Int64
-> Int64 -> CommandProducerSuccess -> CommandProducerSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "lastSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"lastSequenceId") Int64
y CommandProducerSuccess
x)
Bool
required'producerName
Bool
required'requestId
34
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_version"
CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop
(Setter
CommandProducerSuccess CommandProducerSuccess ByteString ByteString
-> ByteString -> CommandProducerSuccess -> CommandProducerSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaVersion") ByteString
y CommandProducerSuccess
x)
Bool
required'producerName
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop
(Setter
CommandProducerSuccess CommandProducerSuccess FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandProducerSuccess
-> CommandProducerSuccess
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandProducerSuccess CommandProducerSuccess FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandProducerSuccess
x)
Bool
required'producerName
Bool
required'requestId
in
Parser CommandProducerSuccess
-> String -> Parser CommandProducerSuccess
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandProducerSuccess
-> Bool -> Bool -> Parser CommandProducerSuccess
loop CommandProducerSuccess
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandProducerSuccess"
buildMessage :: CommandProducerSuccess -> Builder
buildMessage
= \ _x :: CommandProducerSuccess
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64 CommandProducerSuccess CommandProducerSuccess Word64 Word64
-> CommandProducerSuccess -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandProducerSuccess
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike
Text CommandProducerSuccess CommandProducerSuccess Text Text
-> CommandProducerSuccess -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName") CommandProducerSuccess
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int64)
CommandProducerSuccess
CommandProducerSuccess
(Maybe Int64)
(Maybe Int64)
-> CommandProducerSuccess -> Maybe Int64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'lastSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'lastSequenceId") CommandProducerSuccess
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int64 -> Word64) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
CommandProducerSuccess
CommandProducerSuccess
(Maybe ByteString)
(Maybe ByteString)
-> CommandProducerSuccess -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion") CommandProducerSuccess
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandProducerSuccess
CommandProducerSuccess
FieldSet
FieldSet
-> CommandProducerSuccess -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandProducerSuccess
CommandProducerSuccess
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandProducerSuccess
_x)))))
instance Control.DeepSeq.NFData CommandProducerSuccess where
rnf :: CommandProducerSuccess -> ()
rnf
= \ x__ :: CommandProducerSuccess
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducerSuccess -> FieldSet
_CommandProducerSuccess'_unknownFields CommandProducerSuccess
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducerSuccess -> Word64
_CommandProducerSuccess'requestId CommandProducerSuccess
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducerSuccess -> Text
_CommandProducerSuccess'producerName CommandProducerSuccess
x__)
(Maybe Int64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducerSuccess -> Maybe Int64
_CommandProducerSuccess'lastSequenceId CommandProducerSuccess
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandProducerSuccess -> Maybe ByteString
_CommandProducerSuccess'schemaVersion CommandProducerSuccess
x__) ()))))
data CommandReachedEndOfTopic
= CommandReachedEndOfTopic'_constructor {CommandReachedEndOfTopic -> Word64
_CommandReachedEndOfTopic'consumerId :: !Data.Word.Word64,
CommandReachedEndOfTopic -> FieldSet
_CommandReachedEndOfTopic'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
(CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> Eq CommandReachedEndOfTopic
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c/= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
== :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c== :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
Prelude.Eq, Eq CommandReachedEndOfTopic
Eq CommandReachedEndOfTopic =>
(CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Ordering)
-> (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> (CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool)
-> (CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic)
-> (CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic)
-> Ord CommandReachedEndOfTopic
CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Ordering
CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
$cmin :: CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
max :: CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
$cmax :: CommandReachedEndOfTopic
-> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
>= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c>= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
> :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c> :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
<= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c<= :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
< :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
$c< :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Bool
compare :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Ordering
$ccompare :: CommandReachedEndOfTopic -> CommandReachedEndOfTopic -> Ordering
$cp1Ord :: Eq CommandReachedEndOfTopic
Prelude.Ord)
instance Prelude.Show CommandReachedEndOfTopic where
showsPrec :: Int -> CommandReachedEndOfTopic -> ShowS
showsPrec _ __x :: CommandReachedEndOfTopic
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandReachedEndOfTopic -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandReachedEndOfTopic
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandReachedEndOfTopic "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandReachedEndOfTopic
-> f CommandReachedEndOfTopic
fieldOf _
= ((Word64 -> f Word64)
-> CommandReachedEndOfTopic -> f CommandReachedEndOfTopic)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandReachedEndOfTopic
-> f CommandReachedEndOfTopic
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandReachedEndOfTopic -> Word64)
-> (CommandReachedEndOfTopic -> Word64 -> CommandReachedEndOfTopic)
-> Lens
CommandReachedEndOfTopic CommandReachedEndOfTopic Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandReachedEndOfTopic -> Word64
_CommandReachedEndOfTopic'consumerId
(\ x__ :: CommandReachedEndOfTopic
x__ y__ :: Word64
y__ -> CommandReachedEndOfTopic
x__ {_CommandReachedEndOfTopic'consumerId :: Word64
_CommandReachedEndOfTopic'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandReachedEndOfTopic where
messageName :: Proxy CommandReachedEndOfTopic -> Text
messageName _
= String -> Text
Data.Text.pack "pulsar.proto.CommandReachedEndOfTopic"
packedMessageDescriptor :: Proxy CommandReachedEndOfTopic -> ByteString
packedMessageDescriptor _
= "\n\
\\CANCommandReachedEndOfTopic\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId"
packedFileDescriptor :: Proxy CommandReachedEndOfTopic -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandReachedEndOfTopic)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandReachedEndOfTopic
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandReachedEndOfTopic Word64
-> FieldDescriptor CommandReachedEndOfTopic
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandReachedEndOfTopic CommandReachedEndOfTopic Word64 Word64
-> FieldAccessor CommandReachedEndOfTopic Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandReachedEndOfTopic
in
[(Tag, FieldDescriptor CommandReachedEndOfTopic)]
-> Map Tag (FieldDescriptor CommandReachedEndOfTopic)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandReachedEndOfTopic
consumerId__field_descriptor)]
unknownFields :: LensLike' f CommandReachedEndOfTopic FieldSet
unknownFields
= (CommandReachedEndOfTopic -> FieldSet)
-> (CommandReachedEndOfTopic
-> FieldSet -> CommandReachedEndOfTopic)
-> Lens' CommandReachedEndOfTopic FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandReachedEndOfTopic -> FieldSet
_CommandReachedEndOfTopic'_unknownFields
(\ x__ :: CommandReachedEndOfTopic
x__ y__ :: FieldSet
y__ -> CommandReachedEndOfTopic
x__ {_CommandReachedEndOfTopic'_unknownFields :: FieldSet
_CommandReachedEndOfTopic'_unknownFields = FieldSet
y__})
defMessage :: CommandReachedEndOfTopic
defMessage
= $WCommandReachedEndOfTopic'_constructor :: Word64 -> FieldSet -> CommandReachedEndOfTopic
CommandReachedEndOfTopic'_constructor
{_CommandReachedEndOfTopic'consumerId :: Word64
_CommandReachedEndOfTopic'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandReachedEndOfTopic'_unknownFields :: FieldSet
_CommandReachedEndOfTopic'_unknownFields = []}
parseMessage :: Parser CommandReachedEndOfTopic
parseMessage
= let
loop ::
CommandReachedEndOfTopic
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandReachedEndOfTopic
loop :: CommandReachedEndOfTopic -> Bool -> Parser CommandReachedEndOfTopic
loop x :: CommandReachedEndOfTopic
x required'consumerId :: Bool
required'consumerId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandReachedEndOfTopic -> Parser CommandReachedEndOfTopic
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandReachedEndOfTopic CommandReachedEndOfTopic FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandReachedEndOfTopic
-> CommandReachedEndOfTopic
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandReachedEndOfTopic CommandReachedEndOfTopic FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandReachedEndOfTopic
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandReachedEndOfTopic -> Bool -> Parser CommandReachedEndOfTopic
loop
(Setter
CommandReachedEndOfTopic CommandReachedEndOfTopic Word64 Word64
-> Word64 -> CommandReachedEndOfTopic -> CommandReachedEndOfTopic
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandReachedEndOfTopic
x)
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandReachedEndOfTopic -> Bool -> Parser CommandReachedEndOfTopic
loop
(Setter
CommandReachedEndOfTopic CommandReachedEndOfTopic FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandReachedEndOfTopic
-> CommandReachedEndOfTopic
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandReachedEndOfTopic CommandReachedEndOfTopic FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandReachedEndOfTopic
x)
Bool
required'consumerId
in
Parser CommandReachedEndOfTopic
-> String -> Parser CommandReachedEndOfTopic
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandReachedEndOfTopic -> Bool -> Parser CommandReachedEndOfTopic
loop CommandReachedEndOfTopic
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True)
"CommandReachedEndOfTopic"
buildMessage :: CommandReachedEndOfTopic -> Builder
buildMessage
= \ _x :: CommandReachedEndOfTopic
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandReachedEndOfTopic
CommandReachedEndOfTopic
Word64
Word64
-> CommandReachedEndOfTopic -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandReachedEndOfTopic
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandReachedEndOfTopic
CommandReachedEndOfTopic
FieldSet
FieldSet
-> CommandReachedEndOfTopic -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandReachedEndOfTopic
CommandReachedEndOfTopic
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandReachedEndOfTopic
_x))
instance Control.DeepSeq.NFData CommandReachedEndOfTopic where
rnf :: CommandReachedEndOfTopic -> ()
rnf
= \ x__ :: CommandReachedEndOfTopic
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandReachedEndOfTopic -> FieldSet
_CommandReachedEndOfTopic'_unknownFields CommandReachedEndOfTopic
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandReachedEndOfTopic -> Word64
_CommandReachedEndOfTopic'consumerId CommandReachedEndOfTopic
x__) ())
data CommandRedeliverUnacknowledgedMessages
= CommandRedeliverUnacknowledgedMessages'_constructor {CommandRedeliverUnacknowledgedMessages -> Word64
_CommandRedeliverUnacknowledgedMessages'consumerId :: !Data.Word.Word64,
CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds :: !(Data.Vector.Vector MessageIdData),
CommandRedeliverUnacknowledgedMessages -> FieldSet
_CommandRedeliverUnacknowledgedMessages'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
(CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> Eq CommandRedeliverUnacknowledgedMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c/= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
== :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c== :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
Prelude.Eq, Eq CommandRedeliverUnacknowledgedMessages
Eq CommandRedeliverUnacknowledgedMessages =>
(CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Ordering)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages)
-> (CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages)
-> Ord CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Ordering
CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
$cmin :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
max :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
$cmax :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
>= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c>= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
> :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c> :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
<= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c<= :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
< :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
$c< :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Bool
compare :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Ordering
$ccompare :: CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages -> Ordering
$cp1Ord :: Eq CommandRedeliverUnacknowledgedMessages
Prelude.Ord)
instance Prelude.Show CommandRedeliverUnacknowledgedMessages where
showsPrec :: Int -> CommandRedeliverUnacknowledgedMessages -> ShowS
showsPrec _ __x :: CommandRedeliverUnacknowledgedMessages
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandRedeliverUnacknowledgedMessages -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandRedeliverUnacknowledgedMessages
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandRedeliverUnacknowledgedMessages "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
fieldOf _
= ((Word64 -> f Word64)
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandRedeliverUnacknowledgedMessages -> Word64)
-> (CommandRedeliverUnacknowledgedMessages
-> Word64 -> CommandRedeliverUnacknowledgedMessages)
-> Lens
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
Word64
Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandRedeliverUnacknowledgedMessages -> Word64
_CommandRedeliverUnacknowledgedMessages'consumerId
(\ x__ :: CommandRedeliverUnacknowledgedMessages
x__ y__ :: Word64
y__
-> CommandRedeliverUnacknowledgedMessages
x__ {_CommandRedeliverUnacknowledgedMessages'consumerId :: Word64
_CommandRedeliverUnacknowledgedMessages'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandRedeliverUnacknowledgedMessages "messageIds" [MessageIdData] where
fieldOf :: Proxy# "messageIds"
-> ([MessageIdData] -> f [MessageIdData])
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
fieldOf _
= ((Vector MessageIdData -> f (Vector MessageIdData))
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> (([MessageIdData] -> f [MessageIdData])
-> Vector MessageIdData -> f (Vector MessageIdData))
-> ([MessageIdData] -> f [MessageIdData])
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData)
-> (CommandRedeliverUnacknowledgedMessages
-> Vector MessageIdData -> CommandRedeliverUnacknowledgedMessages)
-> Lens
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
(Vector MessageIdData)
(Vector MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds
(\ x__ :: CommandRedeliverUnacknowledgedMessages
x__ y__ :: Vector MessageIdData
y__
-> CommandRedeliverUnacknowledgedMessages
x__ {_CommandRedeliverUnacknowledgedMessages'messageIds :: Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds = Vector MessageIdData
y__}))
((Vector MessageIdData -> [MessageIdData])
-> (Vector MessageIdData
-> [MessageIdData] -> Vector MessageIdData)
-> Lens
(Vector MessageIdData)
(Vector MessageIdData)
[MessageIdData]
[MessageIdData]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector MessageIdData -> [MessageIdData]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [MessageIdData]
y__ -> [MessageIdData] -> Vector MessageIdData
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [MessageIdData]
y__))
instance Data.ProtoLens.Field.HasField CommandRedeliverUnacknowledgedMessages "vec'messageIds" (Data.Vector.Vector MessageIdData) where
fieldOf :: Proxy# "vec'messageIds"
-> (Vector MessageIdData -> f (Vector MessageIdData))
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
fieldOf _
= ((Vector MessageIdData -> f (Vector MessageIdData))
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages)
-> ((Vector MessageIdData -> f (Vector MessageIdData))
-> Vector MessageIdData -> f (Vector MessageIdData))
-> (Vector MessageIdData -> f (Vector MessageIdData))
-> CommandRedeliverUnacknowledgedMessages
-> f CommandRedeliverUnacknowledgedMessages
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData)
-> (CommandRedeliverUnacknowledgedMessages
-> Vector MessageIdData -> CommandRedeliverUnacknowledgedMessages)
-> Lens
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
(Vector MessageIdData)
(Vector MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds
(\ x__ :: CommandRedeliverUnacknowledgedMessages
x__ y__ :: Vector MessageIdData
y__
-> CommandRedeliverUnacknowledgedMessages
x__ {_CommandRedeliverUnacknowledgedMessages'messageIds :: Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds = Vector MessageIdData
y__}))
(Vector MessageIdData -> f (Vector MessageIdData))
-> Vector MessageIdData -> f (Vector MessageIdData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandRedeliverUnacknowledgedMessages where
messageName :: Proxy CommandRedeliverUnacknowledgedMessages -> Text
messageName _
= String -> Text
Data.Text.pack
"pulsar.proto.CommandRedeliverUnacknowledgedMessages"
packedMessageDescriptor :: Proxy CommandRedeliverUnacknowledgedMessages -> ByteString
packedMessageDescriptor _
= "\n\
\&CommandRedeliverUnacknowledgedMessages\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2<\n\
\\vmessage_ids\CAN\STX \ETX(\v2\ESC.pulsar.proto.MessageIdDataR\n\
\messageIds"
packedFileDescriptor :: Proxy CommandRedeliverUnacknowledgedMessages -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandRedeliverUnacknowledgedMessages)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandRedeliverUnacknowledgedMessages
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandRedeliverUnacknowledgedMessages Word64
-> FieldDescriptor CommandRedeliverUnacknowledgedMessages
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
Word64
Word64
-> FieldAccessor CommandRedeliverUnacknowledgedMessages Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandRedeliverUnacknowledgedMessages
messageIds__field_descriptor :: FieldDescriptor CommandRedeliverUnacknowledgedMessages
messageIds__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor
CommandRedeliverUnacknowledgedMessages MessageIdData
-> FieldDescriptor CommandRedeliverUnacknowledgedMessages
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_ids"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(Packing
-> Lens' CommandRedeliverUnacknowledgedMessages [MessageIdData]
-> FieldAccessor
CommandRedeliverUnacknowledgedMessages MessageIdData
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "messageIds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageIds")) ::
Data.ProtoLens.FieldDescriptor CommandRedeliverUnacknowledgedMessages
in
[(Tag, FieldDescriptor CommandRedeliverUnacknowledgedMessages)]
-> Map Tag (FieldDescriptor CommandRedeliverUnacknowledgedMessages)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandRedeliverUnacknowledgedMessages
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandRedeliverUnacknowledgedMessages
messageIds__field_descriptor)]
unknownFields :: LensLike' f CommandRedeliverUnacknowledgedMessages FieldSet
unknownFields
= (CommandRedeliverUnacknowledgedMessages -> FieldSet)
-> (CommandRedeliverUnacknowledgedMessages
-> FieldSet -> CommandRedeliverUnacknowledgedMessages)
-> Lens' CommandRedeliverUnacknowledgedMessages FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandRedeliverUnacknowledgedMessages -> FieldSet
_CommandRedeliverUnacknowledgedMessages'_unknownFields
(\ x__ :: CommandRedeliverUnacknowledgedMessages
x__ y__ :: FieldSet
y__
-> CommandRedeliverUnacknowledgedMessages
x__
{_CommandRedeliverUnacknowledgedMessages'_unknownFields :: FieldSet
_CommandRedeliverUnacknowledgedMessages'_unknownFields = FieldSet
y__})
defMessage :: CommandRedeliverUnacknowledgedMessages
defMessage
= $WCommandRedeliverUnacknowledgedMessages'_constructor :: Word64
-> Vector MessageIdData
-> FieldSet
-> CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages'_constructor
{_CommandRedeliverUnacknowledgedMessages'consumerId :: Word64
_CommandRedeliverUnacknowledgedMessages'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandRedeliverUnacknowledgedMessages'messageIds :: Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds = Vector MessageIdData
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandRedeliverUnacknowledgedMessages'_unknownFields :: FieldSet
_CommandRedeliverUnacknowledgedMessages'_unknownFields = []}
parseMessage :: Parser CommandRedeliverUnacknowledgedMessages
parseMessage
= let
loop ::
CommandRedeliverUnacknowledgedMessages
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld MessageIdData
-> Data.ProtoLens.Encoding.Bytes.Parser CommandRedeliverUnacknowledgedMessages
loop :: CommandRedeliverUnacknowledgedMessages
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Parser CommandRedeliverUnacknowledgedMessages
loop x :: CommandRedeliverUnacknowledgedMessages
x required'consumerId :: Bool
required'consumerId mutable'messageIds :: Growing Vector RealWorld MessageIdData
mutable'messageIds
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector MessageIdData
frozen'messageIds <- IO (Vector MessageIdData) -> Parser (Vector MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) MessageIdData
-> IO (Vector MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld MessageIdData
Growing Vector (PrimState IO) MessageIdData
mutable'messageIds)
(let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandRedeliverUnacknowledgedMessages
-> Parser CommandRedeliverUnacknowledgedMessages
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
(Vector MessageIdData)
(Vector MessageIdData)
-> Vector MessageIdData
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'messageIds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'messageIds")
Vector MessageIdData
frozen'messageIds
CommandRedeliverUnacknowledgedMessages
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandRedeliverUnacknowledgedMessages
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Parser CommandRedeliverUnacknowledgedMessages
loop
(Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
Word64
Word64
-> Word64
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandRedeliverUnacknowledgedMessages
x)
Bool
Prelude.False
Growing Vector RealWorld MessageIdData
mutable'messageIds
18
-> do !MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message_ids"
Growing Vector RealWorld MessageIdData
v <- IO (Growing Vector RealWorld MessageIdData)
-> Parser (Growing Vector RealWorld MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) MessageIdData
-> MessageIdData
-> IO (Growing Vector (PrimState IO) MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld MessageIdData
Growing Vector (PrimState IO) MessageIdData
mutable'messageIds MessageIdData
y)
CommandRedeliverUnacknowledgedMessages
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Parser CommandRedeliverUnacknowledgedMessages
loop CommandRedeliverUnacknowledgedMessages
x Bool
required'consumerId Growing Vector RealWorld MessageIdData
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandRedeliverUnacknowledgedMessages
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Parser CommandRedeliverUnacknowledgedMessages
loop
(Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
-> (FieldSet -> FieldSet)
-> CommandRedeliverUnacknowledgedMessages
-> CommandRedeliverUnacknowledgedMessages
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandRedeliverUnacknowledgedMessages
x)
Bool
required'consumerId
Growing Vector RealWorld MessageIdData
mutable'messageIds
in
Parser CommandRedeliverUnacknowledgedMessages
-> String -> Parser CommandRedeliverUnacknowledgedMessages
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld MessageIdData
mutable'messageIds <- IO (Growing Vector RealWorld MessageIdData)
-> Parser (Growing Vector RealWorld MessageIdData)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld MessageIdData)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandRedeliverUnacknowledgedMessages
-> Bool
-> Growing Vector RealWorld MessageIdData
-> Parser CommandRedeliverUnacknowledgedMessages
loop CommandRedeliverUnacknowledgedMessages
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld MessageIdData
mutable'messageIds)
"CommandRedeliverUnacknowledgedMessages"
buildMessage :: CommandRedeliverUnacknowledgedMessages -> Builder
buildMessage
= \ _x :: CommandRedeliverUnacknowledgedMessages
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike
Word64
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
Word64
Word64
-> CommandRedeliverUnacknowledgedMessages -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandRedeliverUnacknowledgedMessages
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((MessageIdData -> Builder) -> Vector MessageIdData -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: MessageIdData
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
MessageIdData
_v))
(FoldLike
(Vector MessageIdData)
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
(Vector MessageIdData)
(Vector MessageIdData)
-> CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'messageIds" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'messageIds") CommandRedeliverUnacknowledgedMessages
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
-> CommandRedeliverUnacknowledgedMessages -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet
CommandRedeliverUnacknowledgedMessages
CommandRedeliverUnacknowledgedMessages
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandRedeliverUnacknowledgedMessages
_x)))
instance Control.DeepSeq.NFData CommandRedeliverUnacknowledgedMessages where
rnf :: CommandRedeliverUnacknowledgedMessages -> ()
rnf
= \ x__ :: CommandRedeliverUnacknowledgedMessages
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandRedeliverUnacknowledgedMessages -> FieldSet
_CommandRedeliverUnacknowledgedMessages'_unknownFields CommandRedeliverUnacknowledgedMessages
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandRedeliverUnacknowledgedMessages -> Word64
_CommandRedeliverUnacknowledgedMessages'consumerId CommandRedeliverUnacknowledgedMessages
x__)
(Vector MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandRedeliverUnacknowledgedMessages -> Vector MessageIdData
_CommandRedeliverUnacknowledgedMessages'messageIds CommandRedeliverUnacknowledgedMessages
x__) ()))
data CommandSeek
= CommandSeek'_constructor {CommandSeek -> Word64
_CommandSeek'consumerId :: !Data.Word.Word64,
CommandSeek -> Word64
_CommandSeek'requestId :: !Data.Word.Word64,
CommandSeek -> Maybe MessageIdData
_CommandSeek'messageId :: !(Prelude.Maybe MessageIdData),
CommandSeek -> Maybe Word64
_CommandSeek'messagePublishTime :: !(Prelude.Maybe Data.Word.Word64),
CommandSeek -> FieldSet
_CommandSeek'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSeek -> CommandSeek -> Bool
(CommandSeek -> CommandSeek -> Bool)
-> (CommandSeek -> CommandSeek -> Bool) -> Eq CommandSeek
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSeek -> CommandSeek -> Bool
$c/= :: CommandSeek -> CommandSeek -> Bool
== :: CommandSeek -> CommandSeek -> Bool
$c== :: CommandSeek -> CommandSeek -> Bool
Prelude.Eq, Eq CommandSeek
Eq CommandSeek =>
(CommandSeek -> CommandSeek -> Ordering)
-> (CommandSeek -> CommandSeek -> Bool)
-> (CommandSeek -> CommandSeek -> Bool)
-> (CommandSeek -> CommandSeek -> Bool)
-> (CommandSeek -> CommandSeek -> Bool)
-> (CommandSeek -> CommandSeek -> CommandSeek)
-> (CommandSeek -> CommandSeek -> CommandSeek)
-> Ord CommandSeek
CommandSeek -> CommandSeek -> Bool
CommandSeek -> CommandSeek -> Ordering
CommandSeek -> CommandSeek -> CommandSeek
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSeek -> CommandSeek -> CommandSeek
$cmin :: CommandSeek -> CommandSeek -> CommandSeek
max :: CommandSeek -> CommandSeek -> CommandSeek
$cmax :: CommandSeek -> CommandSeek -> CommandSeek
>= :: CommandSeek -> CommandSeek -> Bool
$c>= :: CommandSeek -> CommandSeek -> Bool
> :: CommandSeek -> CommandSeek -> Bool
$c> :: CommandSeek -> CommandSeek -> Bool
<= :: CommandSeek -> CommandSeek -> Bool
$c<= :: CommandSeek -> CommandSeek -> Bool
< :: CommandSeek -> CommandSeek -> Bool
$c< :: CommandSeek -> CommandSeek -> Bool
compare :: CommandSeek -> CommandSeek -> Ordering
$ccompare :: CommandSeek -> CommandSeek -> Ordering
$cp1Ord :: Eq CommandSeek
Prelude.Ord)
instance Prelude.Show CommandSeek where
showsPrec :: Int -> CommandSeek -> ShowS
showsPrec _ __x :: CommandSeek
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSeek -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSeek
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSeek "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64) -> CommandSeek -> f CommandSeek
fieldOf _
= ((Word64 -> f Word64) -> CommandSeek -> f CommandSeek)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Word64)
-> (CommandSeek -> Word64 -> CommandSeek)
-> Lens CommandSeek CommandSeek Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Word64
_CommandSeek'consumerId
(\ x__ :: CommandSeek
x__ y__ :: Word64
y__ -> CommandSeek
x__ {_CommandSeek'consumerId :: Word64
_CommandSeek'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSeek "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandSeek -> f CommandSeek
fieldOf _
= ((Word64 -> f Word64) -> CommandSeek -> f CommandSeek)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Word64)
-> (CommandSeek -> Word64 -> CommandSeek)
-> Lens CommandSeek CommandSeek Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Word64
_CommandSeek'requestId
(\ x__ :: CommandSeek
x__ y__ :: Word64
y__ -> CommandSeek
x__ {_CommandSeek'requestId :: Word64
_CommandSeek'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSeek "messageId" MessageIdData where
fieldOf :: Proxy# "messageId"
-> (MessageIdData -> f MessageIdData)
-> CommandSeek
-> f CommandSeek
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSeek -> f CommandSeek)
-> ((MessageIdData -> f MessageIdData)
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (MessageIdData -> f MessageIdData)
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Maybe MessageIdData)
-> (CommandSeek -> Maybe MessageIdData -> CommandSeek)
-> Lens
CommandSeek CommandSeek (Maybe MessageIdData) (Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Maybe MessageIdData
_CommandSeek'messageId
(\ x__ :: CommandSeek
x__ y__ :: Maybe MessageIdData
y__ -> CommandSeek
x__ {_CommandSeek'messageId :: Maybe MessageIdData
_CommandSeek'messageId = Maybe MessageIdData
y__}))
(MessageIdData -> Lens' (Maybe MessageIdData) MessageIdData
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSeek "maybe'messageId" (Prelude.Maybe MessageIdData) where
fieldOf :: Proxy# "maybe'messageId"
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSeek
-> f CommandSeek
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSeek -> f CommandSeek)
-> ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Maybe MessageIdData)
-> (CommandSeek -> Maybe MessageIdData -> CommandSeek)
-> Lens
CommandSeek CommandSeek (Maybe MessageIdData) (Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Maybe MessageIdData
_CommandSeek'messageId
(\ x__ :: CommandSeek
x__ y__ :: Maybe MessageIdData
y__ -> CommandSeek
x__ {_CommandSeek'messageId :: Maybe MessageIdData
_CommandSeek'messageId = Maybe MessageIdData
y__}))
(Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSeek "messagePublishTime" Data.Word.Word64 where
fieldOf :: Proxy# "messagePublishTime"
-> (Word64 -> f Word64) -> CommandSeek -> f CommandSeek
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSeek -> f CommandSeek)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Maybe Word64)
-> (CommandSeek -> Maybe Word64 -> CommandSeek)
-> Lens CommandSeek CommandSeek (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Maybe Word64
_CommandSeek'messagePublishTime
(\ x__ :: CommandSeek
x__ y__ :: Maybe Word64
y__ -> CommandSeek
x__ {_CommandSeek'messagePublishTime :: Maybe Word64
_CommandSeek'messagePublishTime = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandSeek "maybe'messagePublishTime" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'messagePublishTime"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSeek
-> f CommandSeek
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSeek -> f CommandSeek)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSeek
-> f CommandSeek
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSeek -> Maybe Word64)
-> (CommandSeek -> Maybe Word64 -> CommandSeek)
-> Lens CommandSeek CommandSeek (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> Maybe Word64
_CommandSeek'messagePublishTime
(\ x__ :: CommandSeek
x__ y__ :: Maybe Word64
y__ -> CommandSeek
x__ {_CommandSeek'messagePublishTime :: Maybe Word64
_CommandSeek'messagePublishTime = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSeek where
messageName :: Proxy CommandSeek -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSeek"
packedMessageDescriptor :: Proxy CommandSeek -> ByteString
packedMessageDescriptor _
= "\n\
\\vCommandSeek\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2:\n\
\\n\
\message_id\CAN\ETX \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC20\n\
\\DC4message_publish_time\CAN\EOT \SOH(\EOTR\DC2messagePublishTime"
packedFileDescriptor :: Proxy CommandSeek -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSeek)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandSeek
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSeek Word64
-> FieldDescriptor CommandSeek
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSeek CommandSeek Word64 Word64
-> FieldAccessor CommandSeek Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandSeek
requestId__field_descriptor :: FieldDescriptor CommandSeek
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSeek Word64
-> FieldDescriptor CommandSeek
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSeek CommandSeek Word64 Word64
-> FieldAccessor CommandSeek Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandSeek
messageId__field_descriptor :: FieldDescriptor CommandSeek
messageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandSeek MessageIdData
-> FieldDescriptor CommandSeek
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(Lens
CommandSeek CommandSeek (Maybe MessageIdData) (Maybe MessageIdData)
-> FieldAccessor CommandSeek MessageIdData
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messageId")) ::
Data.ProtoLens.FieldDescriptor CommandSeek
messagePublishTime__field_descriptor :: FieldDescriptor CommandSeek
messagePublishTime__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSeek Word64
-> FieldDescriptor CommandSeek
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_publish_time"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandSeek CommandSeek (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSeek Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'messagePublishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messagePublishTime")) ::
Data.ProtoLens.FieldDescriptor CommandSeek
in
[(Tag, FieldDescriptor CommandSeek)]
-> Map Tag (FieldDescriptor CommandSeek)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSeek
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSeek
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandSeek
messageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandSeek
messagePublishTime__field_descriptor)]
unknownFields :: LensLike' f CommandSeek FieldSet
unknownFields
= (CommandSeek -> FieldSet)
-> (CommandSeek -> FieldSet -> CommandSeek)
-> Lens' CommandSeek FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSeek -> FieldSet
_CommandSeek'_unknownFields
(\ x__ :: CommandSeek
x__ y__ :: FieldSet
y__ -> CommandSeek
x__ {_CommandSeek'_unknownFields :: FieldSet
_CommandSeek'_unknownFields = FieldSet
y__})
defMessage :: CommandSeek
defMessage
= $WCommandSeek'_constructor :: Word64
-> Word64
-> Maybe MessageIdData
-> Maybe Word64
-> FieldSet
-> CommandSeek
CommandSeek'_constructor
{_CommandSeek'consumerId :: Word64
_CommandSeek'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSeek'requestId :: Word64
_CommandSeek'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSeek'messageId :: Maybe MessageIdData
_CommandSeek'messageId = Maybe MessageIdData
forall a. Maybe a
Prelude.Nothing,
_CommandSeek'messagePublishTime :: Maybe Word64
_CommandSeek'messagePublishTime = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSeek'_unknownFields :: FieldSet
_CommandSeek'_unknownFields = []}
parseMessage :: Parser CommandSeek
parseMessage
= let
loop ::
CommandSeek
-> Prelude.Bool
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser CommandSeek
loop :: CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop x :: CommandSeek
x required'consumerId :: Bool
required'consumerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSeek -> Parser CommandSeek
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSeek CommandSeek FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSeek CommandSeek FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandSeek
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop
(Setter CommandSeek CommandSeek Word64 Word64
-> Word64 -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandSeek
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop
(Setter CommandSeek CommandSeek Word64 Word64
-> Word64 -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandSeek
x)
Bool
required'consumerId
Bool
Prelude.False
26
-> do MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message_id"
CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop
(Setter CommandSeek CommandSeek MessageIdData MessageIdData
-> MessageIdData -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId") MessageIdData
y CommandSeek
x)
Bool
required'consumerId
Bool
required'requestId
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
"message_publish_time"
CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop
(Setter CommandSeek CommandSeek Word64 Word64
-> Word64 -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "messagePublishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messagePublishTime") Word64
y CommandSeek
x)
Bool
required'consumerId
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop
(Setter CommandSeek CommandSeek FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSeek -> CommandSeek
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSeek CommandSeek FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSeek
x)
Bool
required'consumerId
Bool
required'requestId
in
Parser CommandSeek -> String -> Parser CommandSeek
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandSeek -> Bool -> Bool -> Parser CommandSeek
loop CommandSeek
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandSeek"
buildMessage :: CommandSeek -> Builder
buildMessage
= \ _x :: CommandSeek
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSeek CommandSeek Word64 Word64
-> CommandSeek -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandSeek
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSeek CommandSeek Word64 Word64
-> CommandSeek -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandSeek
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe MessageIdData)
CommandSeek
CommandSeek
(Maybe MessageIdData)
(Maybe MessageIdData)
-> CommandSeek -> Maybe MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messageId") CommandSeek
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: MessageIdData
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
MessageIdData
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSeek
CommandSeek
(Maybe Word64)
(Maybe Word64)
-> CommandSeek -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'messagePublishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messagePublishTime") CommandSeek
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandSeek CommandSeek FieldSet FieldSet
-> CommandSeek -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandSeek CommandSeek FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandSeek
_x)))))
instance Control.DeepSeq.NFData CommandSeek where
rnf :: CommandSeek -> ()
rnf
= \ x__ :: CommandSeek
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSeek -> FieldSet
_CommandSeek'_unknownFields CommandSeek
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSeek -> Word64
_CommandSeek'consumerId CommandSeek
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSeek -> Word64
_CommandSeek'requestId CommandSeek
x__)
(Maybe MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSeek -> Maybe MessageIdData
_CommandSeek'messageId CommandSeek
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSeek -> Maybe Word64
_CommandSeek'messagePublishTime CommandSeek
x__) ()))))
data CommandSend
= CommandSend'_constructor {CommandSend -> Word64
_CommandSend'producerId :: !Data.Word.Word64,
CommandSend -> Word64
_CommandSend'sequenceId :: !Data.Word.Word64,
CommandSend -> Maybe Int32
_CommandSend'numMessages :: !(Prelude.Maybe Data.Int.Int32),
CommandSend -> Maybe Word64
_CommandSend'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
CommandSend -> Maybe Word64
_CommandSend'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
CommandSend -> Maybe Word64
_CommandSend'highestSequenceId :: !(Prelude.Maybe Data.Word.Word64),
CommandSend -> Maybe Bool
_CommandSend'isChunk :: !(Prelude.Maybe Prelude.Bool),
CommandSend -> FieldSet
_CommandSend'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSend -> CommandSend -> Bool
(CommandSend -> CommandSend -> Bool)
-> (CommandSend -> CommandSend -> Bool) -> Eq CommandSend
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSend -> CommandSend -> Bool
$c/= :: CommandSend -> CommandSend -> Bool
== :: CommandSend -> CommandSend -> Bool
$c== :: CommandSend -> CommandSend -> Bool
Prelude.Eq, Eq CommandSend
Eq CommandSend =>
(CommandSend -> CommandSend -> Ordering)
-> (CommandSend -> CommandSend -> Bool)
-> (CommandSend -> CommandSend -> Bool)
-> (CommandSend -> CommandSend -> Bool)
-> (CommandSend -> CommandSend -> Bool)
-> (CommandSend -> CommandSend -> CommandSend)
-> (CommandSend -> CommandSend -> CommandSend)
-> Ord CommandSend
CommandSend -> CommandSend -> Bool
CommandSend -> CommandSend -> Ordering
CommandSend -> CommandSend -> CommandSend
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSend -> CommandSend -> CommandSend
$cmin :: CommandSend -> CommandSend -> CommandSend
max :: CommandSend -> CommandSend -> CommandSend
$cmax :: CommandSend -> CommandSend -> CommandSend
>= :: CommandSend -> CommandSend -> Bool
$c>= :: CommandSend -> CommandSend -> Bool
> :: CommandSend -> CommandSend -> Bool
$c> :: CommandSend -> CommandSend -> Bool
<= :: CommandSend -> CommandSend -> Bool
$c<= :: CommandSend -> CommandSend -> Bool
< :: CommandSend -> CommandSend -> Bool
$c< :: CommandSend -> CommandSend -> Bool
compare :: CommandSend -> CommandSend -> Ordering
$ccompare :: CommandSend -> CommandSend -> Ordering
$cp1Ord :: Eq CommandSend
Prelude.Ord)
instance Prelude.Show CommandSend where
showsPrec :: Int -> CommandSend -> ShowS
showsPrec _ __x :: CommandSend
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSend -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSend
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSend "producerId" Data.Word.Word64 where
fieldOf :: Proxy# "producerId"
-> (Word64 -> f Word64) -> CommandSend -> f CommandSend
fieldOf _
= ((Word64 -> f Word64) -> CommandSend -> f CommandSend)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Word64)
-> (CommandSend -> Word64 -> CommandSend)
-> Lens CommandSend CommandSend Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Word64
_CommandSend'producerId
(\ x__ :: CommandSend
x__ y__ :: Word64
y__ -> CommandSend
x__ {_CommandSend'producerId :: Word64
_CommandSend'producerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "sequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "sequenceId"
-> (Word64 -> f Word64) -> CommandSend -> f CommandSend
fieldOf _
= ((Word64 -> f Word64) -> CommandSend -> f CommandSend)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Word64)
-> (CommandSend -> Word64 -> CommandSend)
-> Lens CommandSend CommandSend Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Word64
_CommandSend'sequenceId
(\ x__ :: CommandSend
x__ y__ :: Word64
y__ -> CommandSend
x__ {_CommandSend'sequenceId :: Word64
_CommandSend'sequenceId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "numMessages" Data.Int.Int32 where
fieldOf :: Proxy# "numMessages"
-> (Int32 -> f Int32) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32)) -> CommandSend -> f CommandSend)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Int32)
-> (CommandSend -> Maybe Int32 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Int32
_CommandSend'numMessages
(\ x__ :: CommandSend
x__ y__ :: Maybe Int32
y__ -> CommandSend
x__ {_CommandSend'numMessages :: Maybe Int32
_CommandSend'numMessages = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 1)
instance Data.ProtoLens.Field.HasField CommandSend "maybe'numMessages" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'numMessages"
-> (Maybe Int32 -> f (Maybe Int32)) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32)) -> CommandSend -> f CommandSend)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Int32)
-> (CommandSend -> Maybe Int32 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Int32
_CommandSend'numMessages
(\ x__ :: CommandSend
x__ y__ :: Maybe Int32
y__ -> CommandSend
x__ {_CommandSend'numMessages :: Maybe Int32
_CommandSend'numMessages = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'txnidLeastBits
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'txnidLeastBits :: Maybe Word64
_CommandSend'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandSend "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'txnidLeastBits
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'txnidLeastBits :: Maybe Word64
_CommandSend'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'txnidMostBits
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'txnidMostBits :: Maybe Word64
_CommandSend'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandSend "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'txnidMostBits
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'txnidMostBits :: Maybe Word64
_CommandSend'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "highestSequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "highestSequenceId"
-> (Word64 -> f Word64) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'highestSequenceId
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'highestSequenceId :: Maybe Word64
_CommandSend'highestSequenceId = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandSend "maybe'highestSequenceId" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'highestSequenceId"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSend -> f CommandSend)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Word64)
-> (CommandSend -> Maybe Word64 -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Word64
_CommandSend'highestSequenceId
(\ x__ :: CommandSend
x__ y__ :: Maybe Word64
y__ -> CommandSend
x__ {_CommandSend'highestSequenceId :: Maybe Word64
_CommandSend'highestSequenceId = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSend "isChunk" Prelude.Bool where
fieldOf :: Proxy# "isChunk"
-> (Bool -> f Bool) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Bool -> f (Maybe Bool)) -> CommandSend -> f CommandSend)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Bool)
-> (CommandSend -> Maybe Bool -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Bool
_CommandSend'isChunk
(\ x__ :: CommandSend
x__ y__ :: Maybe Bool
y__ -> CommandSend
x__ {_CommandSend'isChunk :: Maybe Bool
_CommandSend'isChunk = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField CommandSend "maybe'isChunk" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'isChunk"
-> (Maybe Bool -> f (Maybe Bool)) -> CommandSend -> f CommandSend
fieldOf _
= ((Maybe Bool -> f (Maybe Bool)) -> CommandSend -> f CommandSend)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSend
-> f CommandSend
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSend -> Maybe Bool)
-> (CommandSend -> Maybe Bool -> CommandSend)
-> Lens CommandSend CommandSend (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> Maybe Bool
_CommandSend'isChunk
(\ x__ :: CommandSend
x__ y__ :: Maybe Bool
y__ -> CommandSend
x__ {_CommandSend'isChunk :: Maybe Bool
_CommandSend'isChunk = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSend where
messageName :: Proxy CommandSend -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSend"
packedMessageDescriptor :: Proxy CommandSend -> ByteString
packedMessageDescriptor _
= "\n\
\\vCommandSend\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2$\n\
\\fnum_messages\CAN\ETX \SOH(\ENQ:\SOH1R\vnumMessages\DC2+\n\
\\DLEtxnid_least_bits\CAN\EOT \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ENQ \SOH(\EOT:\SOH0R\rtxnidMostBits\DC21\n\
\\DC3highest_sequence_id\CAN\ACK \SOH(\EOT:\SOH0R\DC1highestSequenceId\DC2 \n\
\\bis_chunk\CAN\a \SOH(\b:\ENQfalseR\aisChunk"
packedFileDescriptor :: Proxy CommandSend -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSend)
fieldsByTag
= let
producerId__field_descriptor :: FieldDescriptor CommandSend
producerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSend Word64
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSend CommandSend Word64 Word64
-> FieldAccessor CommandSend Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId")) ::
Data.ProtoLens.FieldDescriptor CommandSend
sequenceId__field_descriptor :: FieldDescriptor CommandSend
sequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSend Word64
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSend CommandSend Word64 Word64
-> FieldAccessor CommandSend Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandSend
numMessages__field_descriptor :: FieldDescriptor CommandSend
numMessages__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandSend Int32
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"num_messages"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens CommandSend CommandSend (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandSend Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'numMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'numMessages")) ::
Data.ProtoLens.FieldDescriptor CommandSend
txnidLeastBits__field_descriptor :: FieldDescriptor CommandSend
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSend Word64
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSend Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor CommandSend
txnidMostBits__field_descriptor :: FieldDescriptor CommandSend
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSend Word64
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSend Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor CommandSend
highestSequenceId__field_descriptor :: FieldDescriptor CommandSend
highestSequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSend Word64
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"highest_sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens CommandSend CommandSend (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSend Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'highestSequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandSend
isChunk__field_descriptor :: FieldDescriptor CommandSend
isChunk__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandSend Bool
-> FieldDescriptor CommandSend
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"is_chunk"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandSend CommandSend (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandSend Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'isChunk" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'isChunk")) ::
Data.ProtoLens.FieldDescriptor CommandSend
in
[(Tag, FieldDescriptor CommandSend)]
-> Map Tag (FieldDescriptor CommandSend)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSend
producerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSend
sequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandSend
numMessages__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandSend
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandSend
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandSend
highestSequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandSend
isChunk__field_descriptor)]
unknownFields :: LensLike' f CommandSend FieldSet
unknownFields
= (CommandSend -> FieldSet)
-> (CommandSend -> FieldSet -> CommandSend)
-> Lens' CommandSend FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSend -> FieldSet
_CommandSend'_unknownFields
(\ x__ :: CommandSend
x__ y__ :: FieldSet
y__ -> CommandSend
x__ {_CommandSend'_unknownFields :: FieldSet
_CommandSend'_unknownFields = FieldSet
y__})
defMessage :: CommandSend
defMessage
= $WCommandSend'_constructor :: Word64
-> Word64
-> Maybe Int32
-> Maybe Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe Bool
-> FieldSet
-> CommandSend
CommandSend'_constructor
{_CommandSend'producerId :: Word64
_CommandSend'producerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSend'sequenceId :: Word64
_CommandSend'sequenceId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSend'numMessages :: Maybe Int32
_CommandSend'numMessages = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandSend'txnidLeastBits :: Maybe Word64
_CommandSend'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSend'txnidMostBits :: Maybe Word64
_CommandSend'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSend'highestSequenceId :: Maybe Word64
_CommandSend'highestSequenceId = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSend'isChunk :: Maybe Bool
_CommandSend'isChunk = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandSend'_unknownFields :: FieldSet
_CommandSend'_unknownFields = []}
parseMessage :: Parser CommandSend
parseMessage
= let
loop ::
CommandSend
-> Prelude.Bool
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser CommandSend
loop :: CommandSend -> Bool -> Bool -> Parser CommandSend
loop x :: CommandSend
x required'producerId :: Bool
required'producerId required'sequenceId :: Bool
required'sequenceId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'producerId then (:) "producer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'sequenceId then (:) "sequence_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSend -> Parser CommandSend
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSend CommandSend FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSend CommandSend FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandSend
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "producer_id"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Word64 Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") Word64
y CommandSend
x)
Bool
Prelude.False
Bool
required'sequenceId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "sequence_id"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Word64 Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") Word64
y CommandSend
x)
Bool
required'producerId
Bool
Prelude.False
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"num_messages"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Int32 Int32
-> Int32 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "numMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"numMessages") Int32
y CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Word64 Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
40
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Word64 Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
48
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "highest_sequence_id"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Word64 Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"highestSequenceId") Word64
y CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
56
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"is_chunk"
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend Bool Bool
-> Bool -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "isChunk" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"isChunk") Bool
y CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSend -> Bool -> Bool -> Parser CommandSend
loop
(Setter CommandSend CommandSend FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSend -> CommandSend
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSend CommandSend FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSend
x)
Bool
required'producerId
Bool
required'sequenceId
in
Parser CommandSend -> String -> Parser CommandSend
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandSend -> Bool -> Bool -> Parser CommandSend
loop CommandSend
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandSend"
buildMessage :: CommandSend -> Builder
buildMessage
= \ _x :: CommandSend
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSend CommandSend Word64 Word64
-> CommandSend -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") CommandSend
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSend CommandSend Word64 Word64
-> CommandSend -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") CommandSend
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32) CommandSend CommandSend (Maybe Int32) (Maybe Int32)
-> CommandSend -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'numMessages" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'numMessages") CommandSend
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSend
CommandSend
(Maybe Word64)
(Maybe Word64)
-> CommandSend -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits") CommandSend
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSend
CommandSend
(Maybe Word64)
(Maybe Word64)
-> CommandSend -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits") CommandSend
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSend
CommandSend
(Maybe Word64)
(Maybe Word64)
-> CommandSend -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'highestSequenceId") CommandSend
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 48)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool) CommandSend CommandSend (Maybe Bool) (Maybe Bool)
-> CommandSend -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'isChunk" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'isChunk") CommandSend
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 56)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandSend CommandSend FieldSet FieldSet
-> CommandSend -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandSend CommandSend FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandSend
_x))))))))
instance Control.DeepSeq.NFData CommandSend where
rnf :: CommandSend -> ()
rnf
= \ x__ :: CommandSend
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> FieldSet
_CommandSend'_unknownFields CommandSend
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Word64
_CommandSend'producerId CommandSend
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Word64
_CommandSend'sequenceId CommandSend
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Maybe Int32
_CommandSend'numMessages CommandSend
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Maybe Word64
_CommandSend'txnidLeastBits CommandSend
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Maybe Word64
_CommandSend'txnidMostBits CommandSend
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSend -> Maybe Word64
_CommandSend'highestSequenceId CommandSend
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandSend -> Maybe Bool
_CommandSend'isChunk CommandSend
x__) ())))))))
data CommandSendError
= CommandSendError'_constructor {CommandSendError -> Word64
_CommandSendError'producerId :: !Data.Word.Word64,
CommandSendError -> Word64
_CommandSendError'sequenceId :: !Data.Word.Word64,
CommandSendError -> ServerError
_CommandSendError'error :: !ServerError,
CommandSendError -> Text
_CommandSendError'message :: !Data.Text.Text,
CommandSendError -> FieldSet
_CommandSendError'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSendError -> CommandSendError -> Bool
(CommandSendError -> CommandSendError -> Bool)
-> (CommandSendError -> CommandSendError -> Bool)
-> Eq CommandSendError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSendError -> CommandSendError -> Bool
$c/= :: CommandSendError -> CommandSendError -> Bool
== :: CommandSendError -> CommandSendError -> Bool
$c== :: CommandSendError -> CommandSendError -> Bool
Prelude.Eq, Eq CommandSendError
Eq CommandSendError =>
(CommandSendError -> CommandSendError -> Ordering)
-> (CommandSendError -> CommandSendError -> Bool)
-> (CommandSendError -> CommandSendError -> Bool)
-> (CommandSendError -> CommandSendError -> Bool)
-> (CommandSendError -> CommandSendError -> Bool)
-> (CommandSendError -> CommandSendError -> CommandSendError)
-> (CommandSendError -> CommandSendError -> CommandSendError)
-> Ord CommandSendError
CommandSendError -> CommandSendError -> Bool
CommandSendError -> CommandSendError -> Ordering
CommandSendError -> CommandSendError -> CommandSendError
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSendError -> CommandSendError -> CommandSendError
$cmin :: CommandSendError -> CommandSendError -> CommandSendError
max :: CommandSendError -> CommandSendError -> CommandSendError
$cmax :: CommandSendError -> CommandSendError -> CommandSendError
>= :: CommandSendError -> CommandSendError -> Bool
$c>= :: CommandSendError -> CommandSendError -> Bool
> :: CommandSendError -> CommandSendError -> Bool
$c> :: CommandSendError -> CommandSendError -> Bool
<= :: CommandSendError -> CommandSendError -> Bool
$c<= :: CommandSendError -> CommandSendError -> Bool
< :: CommandSendError -> CommandSendError -> Bool
$c< :: CommandSendError -> CommandSendError -> Bool
compare :: CommandSendError -> CommandSendError -> Ordering
$ccompare :: CommandSendError -> CommandSendError -> Ordering
$cp1Ord :: Eq CommandSendError
Prelude.Ord)
instance Prelude.Show CommandSendError where
showsPrec :: Int -> CommandSendError -> ShowS
showsPrec _ __x :: CommandSendError
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSendError -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSendError
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSendError "producerId" Data.Word.Word64 where
fieldOf :: Proxy# "producerId"
-> (Word64 -> f Word64) -> CommandSendError -> f CommandSendError
fieldOf _
= ((Word64 -> f Word64) -> CommandSendError -> f CommandSendError)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSendError
-> f CommandSendError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendError -> Word64)
-> (CommandSendError -> Word64 -> CommandSendError)
-> Lens CommandSendError CommandSendError Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendError -> Word64
_CommandSendError'producerId
(\ x__ :: CommandSendError
x__ y__ :: Word64
y__ -> CommandSendError
x__ {_CommandSendError'producerId :: Word64
_CommandSendError'producerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendError "sequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "sequenceId"
-> (Word64 -> f Word64) -> CommandSendError -> f CommandSendError
fieldOf _
= ((Word64 -> f Word64) -> CommandSendError -> f CommandSendError)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSendError
-> f CommandSendError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendError -> Word64)
-> (CommandSendError -> Word64 -> CommandSendError)
-> Lens CommandSendError CommandSendError Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendError -> Word64
_CommandSendError'sequenceId
(\ x__ :: CommandSendError
x__ y__ :: Word64
y__ -> CommandSendError
x__ {_CommandSendError'sequenceId :: Word64
_CommandSendError'sequenceId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendError "error" ServerError where
fieldOf :: Proxy# "error"
-> (ServerError -> f ServerError)
-> CommandSendError
-> f CommandSendError
fieldOf _
= ((ServerError -> f ServerError)
-> CommandSendError -> f CommandSendError)
-> ((ServerError -> f ServerError) -> ServerError -> f ServerError)
-> (ServerError -> f ServerError)
-> CommandSendError
-> f CommandSendError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendError -> ServerError)
-> (CommandSendError -> ServerError -> CommandSendError)
-> Lens CommandSendError CommandSendError ServerError ServerError
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendError -> ServerError
_CommandSendError'error
(\ x__ :: CommandSendError
x__ y__ :: ServerError
y__ -> CommandSendError
x__ {_CommandSendError'error :: ServerError
_CommandSendError'error = ServerError
y__}))
(ServerError -> f ServerError) -> ServerError -> f ServerError
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendError "message" Data.Text.Text where
fieldOf :: Proxy# "message"
-> (Text -> f Text) -> CommandSendError -> f CommandSendError
fieldOf _
= ((Text -> f Text) -> CommandSendError -> f CommandSendError)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandSendError
-> f CommandSendError
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendError -> Text)
-> (CommandSendError -> Text -> CommandSendError)
-> Lens CommandSendError CommandSendError Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendError -> Text
_CommandSendError'message
(\ x__ :: CommandSendError
x__ y__ :: Text
y__ -> CommandSendError
x__ {_CommandSendError'message :: Text
_CommandSendError'message = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSendError where
messageName :: Proxy CommandSendError -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSendError"
packedMessageDescriptor :: Proxy CommandSendError -> ByteString
packedMessageDescriptor _
= "\n\
\\DLECommandSendError\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2/\n\
\\ENQerror\CAN\ETX \STX(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\EOT \STX(\tR\amessage"
packedFileDescriptor :: Proxy CommandSendError -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSendError)
fieldsByTag
= let
producerId__field_descriptor :: FieldDescriptor CommandSendError
producerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSendError Word64
-> FieldDescriptor CommandSendError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSendError CommandSendError Word64 Word64
-> FieldAccessor CommandSendError Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId")) ::
Data.ProtoLens.FieldDescriptor CommandSendError
sequenceId__field_descriptor :: FieldDescriptor CommandSendError
sequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSendError Word64
-> FieldDescriptor CommandSendError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSendError CommandSendError Word64 Word64
-> FieldAccessor CommandSendError Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandSendError
error__field_descriptor :: FieldDescriptor CommandSendError
error__field_descriptor
= String
-> FieldTypeDescriptor ServerError
-> FieldAccessor CommandSendError ServerError
-> FieldDescriptor CommandSendError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"error"
(ScalarField ServerError -> FieldTypeDescriptor ServerError
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ServerError
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor ServerError)
(WireDefault ServerError
-> Lens CommandSendError CommandSendError ServerError ServerError
-> FieldAccessor CommandSendError ServerError
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ServerError
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error")) ::
Data.ProtoLens.FieldDescriptor CommandSendError
message__field_descriptor :: FieldDescriptor CommandSendError
message__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandSendError Text
-> FieldDescriptor CommandSendError
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandSendError CommandSendError Text Text
-> FieldAccessor CommandSendError Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message")) ::
Data.ProtoLens.FieldDescriptor CommandSendError
in
[(Tag, FieldDescriptor CommandSendError)]
-> Map Tag (FieldDescriptor CommandSendError)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSendError
producerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSendError
sequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandSendError
error__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandSendError
message__field_descriptor)]
unknownFields :: LensLike' f CommandSendError FieldSet
unknownFields
= (CommandSendError -> FieldSet)
-> (CommandSendError -> FieldSet -> CommandSendError)
-> Lens' CommandSendError FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendError -> FieldSet
_CommandSendError'_unknownFields
(\ x__ :: CommandSendError
x__ y__ :: FieldSet
y__ -> CommandSendError
x__ {_CommandSendError'_unknownFields :: FieldSet
_CommandSendError'_unknownFields = FieldSet
y__})
defMessage :: CommandSendError
defMessage
= $WCommandSendError'_constructor :: Word64
-> Word64 -> ServerError -> Text -> FieldSet -> CommandSendError
CommandSendError'_constructor
{_CommandSendError'producerId :: Word64
_CommandSendError'producerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendError'sequenceId :: Word64
_CommandSendError'sequenceId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendError'error :: ServerError
_CommandSendError'error = ServerError
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendError'message :: Text
_CommandSendError'message = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendError'_unknownFields :: FieldSet
_CommandSendError'_unknownFields = []}
parseMessage :: Parser CommandSendError
parseMessage
= let
loop ::
CommandSendError
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandSendError
loop :: CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
x :: CommandSendError
x
required'error :: Bool
required'error
required'message :: Bool
required'message
required'producerId :: Bool
required'producerId
required'sequenceId :: Bool
required'sequenceId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'error then (:) "error" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'message then (:) "message" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'producerId then (:) "producer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'sequenceId then
(:) "sequence_id"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
[])))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSendError -> Parser CommandSendError
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSendError CommandSendError FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSendError CommandSendError FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandSendError
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "producer_id"
CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
(Setter CommandSendError CommandSendError Word64 Word64
-> Word64 -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") Word64
y CommandSendError
x)
Bool
required'error
Bool
required'message
Bool
Prelude.False
Bool
required'sequenceId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "sequence_id"
CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
(Setter CommandSendError CommandSendError Word64 Word64
-> Word64 -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") Word64
y CommandSendError
x)
Bool
required'error
Bool
required'message
Bool
required'producerId
Bool
Prelude.False
24
-> do ServerError
y <- Parser ServerError -> String -> Parser ServerError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> ServerError) -> Parser Int -> Parser ServerError
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> ServerError
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"error"
CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
(Setter CommandSendError CommandSendError ServerError ServerError
-> ServerError -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") ServerError
y CommandSendError
x)
Bool
Prelude.False
Bool
required'message
Bool
required'producerId
Bool
required'sequenceId
34
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"message"
CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
(Setter CommandSendError CommandSendError Text Text
-> Text -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y CommandSendError
x)
Bool
required'error
Bool
Prelude.False
Bool
required'producerId
Bool
required'sequenceId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
(Setter CommandSendError CommandSendError FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSendError -> CommandSendError
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSendError CommandSendError FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSendError
x)
Bool
required'error
Bool
required'message
Bool
required'producerId
Bool
required'sequenceId
in
Parser CommandSendError -> String -> Parser CommandSendError
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandSendError
-> Bool -> Bool -> Bool -> Bool -> Parser CommandSendError
loop
CommandSendError
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True)
"CommandSendError"
buildMessage :: CommandSendError -> Builder
buildMessage
= \ _x :: CommandSendError
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSendError CommandSendError Word64 Word64
-> CommandSendError -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") CommandSendError
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSendError CommandSendError Word64 Word64
-> CommandSendError -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") CommandSendError
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Int -> Builder) -> (ServerError -> Int) -> ServerError -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
ServerError -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
ServerError
CommandSendError
CommandSendError
ServerError
ServerError
-> CommandSendError -> ServerError
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "error" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"error") CommandSendError
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandSendError CommandSendError Text Text
-> CommandSendError -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") CommandSendError
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandSendError CommandSendError FieldSet FieldSet
-> CommandSendError -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandSendError CommandSendError FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandSendError
_x)))))
instance Control.DeepSeq.NFData CommandSendError where
rnf :: CommandSendError -> ()
rnf
= \ x__ :: CommandSendError
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendError -> FieldSet
_CommandSendError'_unknownFields CommandSendError
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendError -> Word64
_CommandSendError'producerId CommandSendError
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendError -> Word64
_CommandSendError'sequenceId CommandSendError
x__)
(ServerError -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendError -> ServerError
_CommandSendError'error CommandSendError
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandSendError -> Text
_CommandSendError'message CommandSendError
x__) ()))))
data CommandSendReceipt
= CommandSendReceipt'_constructor {CommandSendReceipt -> Word64
_CommandSendReceipt'producerId :: !Data.Word.Word64,
CommandSendReceipt -> Word64
_CommandSendReceipt'sequenceId :: !Data.Word.Word64,
CommandSendReceipt -> Maybe MessageIdData
_CommandSendReceipt'messageId :: !(Prelude.Maybe MessageIdData),
CommandSendReceipt -> Maybe Word64
_CommandSendReceipt'highestSequenceId :: !(Prelude.Maybe Data.Word.Word64),
CommandSendReceipt -> FieldSet
_CommandSendReceipt'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSendReceipt -> CommandSendReceipt -> Bool
(CommandSendReceipt -> CommandSendReceipt -> Bool)
-> (CommandSendReceipt -> CommandSendReceipt -> Bool)
-> Eq CommandSendReceipt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c/= :: CommandSendReceipt -> CommandSendReceipt -> Bool
== :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c== :: CommandSendReceipt -> CommandSendReceipt -> Bool
Prelude.Eq, Eq CommandSendReceipt
Eq CommandSendReceipt =>
(CommandSendReceipt -> CommandSendReceipt -> Ordering)
-> (CommandSendReceipt -> CommandSendReceipt -> Bool)
-> (CommandSendReceipt -> CommandSendReceipt -> Bool)
-> (CommandSendReceipt -> CommandSendReceipt -> Bool)
-> (CommandSendReceipt -> CommandSendReceipt -> Bool)
-> (CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt)
-> (CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt)
-> Ord CommandSendReceipt
CommandSendReceipt -> CommandSendReceipt -> Bool
CommandSendReceipt -> CommandSendReceipt -> Ordering
CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt
$cmin :: CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt
max :: CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt
$cmax :: CommandSendReceipt -> CommandSendReceipt -> CommandSendReceipt
>= :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c>= :: CommandSendReceipt -> CommandSendReceipt -> Bool
> :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c> :: CommandSendReceipt -> CommandSendReceipt -> Bool
<= :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c<= :: CommandSendReceipt -> CommandSendReceipt -> Bool
< :: CommandSendReceipt -> CommandSendReceipt -> Bool
$c< :: CommandSendReceipt -> CommandSendReceipt -> Bool
compare :: CommandSendReceipt -> CommandSendReceipt -> Ordering
$ccompare :: CommandSendReceipt -> CommandSendReceipt -> Ordering
$cp1Ord :: Eq CommandSendReceipt
Prelude.Ord)
instance Prelude.Show CommandSendReceipt where
showsPrec :: Int -> CommandSendReceipt -> ShowS
showsPrec _ __x :: CommandSendReceipt
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSendReceipt -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSendReceipt
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSendReceipt "producerId" Data.Word.Word64 where
fieldOf :: Proxy# "producerId"
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Word64 -> f Word64)
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Word64)
-> (CommandSendReceipt -> Word64 -> CommandSendReceipt)
-> Lens CommandSendReceipt CommandSendReceipt Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Word64
_CommandSendReceipt'producerId
(\ x__ :: CommandSendReceipt
x__ y__ :: Word64
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'producerId :: Word64
_CommandSendReceipt'producerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendReceipt "sequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "sequenceId"
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Word64 -> f Word64)
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Word64)
-> (CommandSendReceipt -> Word64 -> CommandSendReceipt)
-> Lens CommandSendReceipt CommandSendReceipt Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Word64
_CommandSendReceipt'sequenceId
(\ x__ :: CommandSendReceipt
x__ y__ :: Word64
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'sequenceId :: Word64
_CommandSendReceipt'sequenceId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendReceipt "messageId" MessageIdData where
fieldOf :: Proxy# "messageId"
-> (MessageIdData -> f MessageIdData)
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((MessageIdData -> f MessageIdData)
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (MessageIdData -> f MessageIdData)
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Maybe MessageIdData)
-> (CommandSendReceipt
-> Maybe MessageIdData -> CommandSendReceipt)
-> Lens
CommandSendReceipt
CommandSendReceipt
(Maybe MessageIdData)
(Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Maybe MessageIdData
_CommandSendReceipt'messageId
(\ x__ :: CommandSendReceipt
x__ y__ :: Maybe MessageIdData
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'messageId :: Maybe MessageIdData
_CommandSendReceipt'messageId = Maybe MessageIdData
y__}))
(MessageIdData -> Lens' (Maybe MessageIdData) MessageIdData
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSendReceipt "maybe'messageId" (Prelude.Maybe MessageIdData) where
fieldOf :: Proxy# "maybe'messageId"
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Maybe MessageIdData)
-> (CommandSendReceipt
-> Maybe MessageIdData -> CommandSendReceipt)
-> Lens
CommandSendReceipt
CommandSendReceipt
(Maybe MessageIdData)
(Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Maybe MessageIdData
_CommandSendReceipt'messageId
(\ x__ :: CommandSendReceipt
x__ y__ :: Maybe MessageIdData
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'messageId :: Maybe MessageIdData
_CommandSendReceipt'messageId = Maybe MessageIdData
y__}))
(Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSendReceipt "highestSequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "highestSequenceId"
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Maybe Word64)
-> (CommandSendReceipt -> Maybe Word64 -> CommandSendReceipt)
-> Lens
CommandSendReceipt CommandSendReceipt (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Maybe Word64
_CommandSendReceipt'highestSequenceId
(\ x__ :: CommandSendReceipt
x__ y__ :: Maybe Word64
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'highestSequenceId :: Maybe Word64
_CommandSendReceipt'highestSequenceId = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandSendReceipt "maybe'highestSequenceId" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'highestSequenceId"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSendReceipt
-> f CommandSendReceipt
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSendReceipt -> f CommandSendReceipt)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSendReceipt
-> f CommandSendReceipt
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSendReceipt -> Maybe Word64)
-> (CommandSendReceipt -> Maybe Word64 -> CommandSendReceipt)
-> Lens
CommandSendReceipt CommandSendReceipt (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> Maybe Word64
_CommandSendReceipt'highestSequenceId
(\ x__ :: CommandSendReceipt
x__ y__ :: Maybe Word64
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'highestSequenceId :: Maybe Word64
_CommandSendReceipt'highestSequenceId = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSendReceipt where
messageName :: Proxy CommandSendReceipt -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSendReceipt"
packedMessageDescriptor :: Proxy CommandSendReceipt -> ByteString
packedMessageDescriptor _
= "\n\
\\DC2CommandSendReceipt\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2:\n\
\\n\
\message_id\CAN\ETX \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC21\n\
\\DC3highest_sequence_id\CAN\EOT \SOH(\EOT:\SOH0R\DC1highestSequenceId"
packedFileDescriptor :: Proxy CommandSendReceipt -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSendReceipt)
fieldsByTag
= let
producerId__field_descriptor :: FieldDescriptor CommandSendReceipt
producerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSendReceipt Word64
-> FieldDescriptor CommandSendReceipt
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSendReceipt CommandSendReceipt Word64 Word64
-> FieldAccessor CommandSendReceipt Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId")) ::
Data.ProtoLens.FieldDescriptor CommandSendReceipt
sequenceId__field_descriptor :: FieldDescriptor CommandSendReceipt
sequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSendReceipt Word64
-> FieldDescriptor CommandSendReceipt
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSendReceipt CommandSendReceipt Word64 Word64
-> FieldAccessor CommandSendReceipt Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandSendReceipt
messageId__field_descriptor :: FieldDescriptor CommandSendReceipt
messageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandSendReceipt MessageIdData
-> FieldDescriptor CommandSendReceipt
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(Lens
CommandSendReceipt
CommandSendReceipt
(Maybe MessageIdData)
(Maybe MessageIdData)
-> FieldAccessor CommandSendReceipt MessageIdData
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messageId")) ::
Data.ProtoLens.FieldDescriptor CommandSendReceipt
highestSequenceId__field_descriptor :: FieldDescriptor CommandSendReceipt
highestSequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSendReceipt Word64
-> FieldDescriptor CommandSendReceipt
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"highest_sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandSendReceipt CommandSendReceipt (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSendReceipt Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'highestSequenceId")) ::
Data.ProtoLens.FieldDescriptor CommandSendReceipt
in
[(Tag, FieldDescriptor CommandSendReceipt)]
-> Map Tag (FieldDescriptor CommandSendReceipt)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSendReceipt
producerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSendReceipt
sequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandSendReceipt
messageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandSendReceipt
highestSequenceId__field_descriptor)]
unknownFields :: LensLike' f CommandSendReceipt FieldSet
unknownFields
= (CommandSendReceipt -> FieldSet)
-> (CommandSendReceipt -> FieldSet -> CommandSendReceipt)
-> Lens' CommandSendReceipt FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSendReceipt -> FieldSet
_CommandSendReceipt'_unknownFields
(\ x__ :: CommandSendReceipt
x__ y__ :: FieldSet
y__ -> CommandSendReceipt
x__ {_CommandSendReceipt'_unknownFields :: FieldSet
_CommandSendReceipt'_unknownFields = FieldSet
y__})
defMessage :: CommandSendReceipt
defMessage
= $WCommandSendReceipt'_constructor :: Word64
-> Word64
-> Maybe MessageIdData
-> Maybe Word64
-> FieldSet
-> CommandSendReceipt
CommandSendReceipt'_constructor
{_CommandSendReceipt'producerId :: Word64
_CommandSendReceipt'producerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendReceipt'sequenceId :: Word64
_CommandSendReceipt'sequenceId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSendReceipt'messageId :: Maybe MessageIdData
_CommandSendReceipt'messageId = Maybe MessageIdData
forall a. Maybe a
Prelude.Nothing,
_CommandSendReceipt'highestSequenceId :: Maybe Word64
_CommandSendReceipt'highestSequenceId = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSendReceipt'_unknownFields :: FieldSet
_CommandSendReceipt'_unknownFields = []}
parseMessage :: Parser CommandSendReceipt
parseMessage
= let
loop ::
CommandSendReceipt
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandSendReceipt
loop :: CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop x :: CommandSendReceipt
x required'producerId :: Bool
required'producerId required'sequenceId :: Bool
required'sequenceId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'producerId then (:) "producer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'sequenceId then (:) "sequence_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSendReceipt -> Parser CommandSendReceipt
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSendReceipt CommandSendReceipt FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandSendReceipt
-> CommandSendReceipt
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSendReceipt CommandSendReceipt FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandSendReceipt
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "producer_id"
CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop
(Setter CommandSendReceipt CommandSendReceipt Word64 Word64
-> Word64 -> CommandSendReceipt -> CommandSendReceipt
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") Word64
y CommandSendReceipt
x)
Bool
Prelude.False
Bool
required'sequenceId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "sequence_id"
CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop
(Setter CommandSendReceipt CommandSendReceipt Word64 Word64
-> Word64 -> CommandSendReceipt -> CommandSendReceipt
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") Word64
y CommandSendReceipt
x)
Bool
required'producerId
Bool
Prelude.False
26
-> do MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"message_id"
CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop
(Setter
CommandSendReceipt CommandSendReceipt MessageIdData MessageIdData
-> MessageIdData -> CommandSendReceipt -> CommandSendReceipt
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"messageId") MessageIdData
y CommandSendReceipt
x)
Bool
required'producerId
Bool
required'sequenceId
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "highest_sequence_id"
CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop
(Setter CommandSendReceipt CommandSendReceipt Word64 Word64
-> Word64 -> CommandSendReceipt -> CommandSendReceipt
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"highestSequenceId") Word64
y CommandSendReceipt
x)
Bool
required'producerId
Bool
required'sequenceId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop
(Setter CommandSendReceipt CommandSendReceipt FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandSendReceipt
-> CommandSendReceipt
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSendReceipt CommandSendReceipt FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSendReceipt
x)
Bool
required'producerId
Bool
required'sequenceId
in
Parser CommandSendReceipt -> String -> Parser CommandSendReceipt
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandSendReceipt -> Bool -> Bool -> Parser CommandSendReceipt
loop CommandSendReceipt
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandSendReceipt"
buildMessage :: CommandSendReceipt -> Builder
buildMessage
= \ _x :: CommandSendReceipt
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSendReceipt CommandSendReceipt Word64 Word64
-> CommandSendReceipt -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "producerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerId") CommandSendReceipt
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSendReceipt CommandSendReceipt Word64 Word64
-> CommandSendReceipt -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") CommandSendReceipt
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe MessageIdData)
CommandSendReceipt
CommandSendReceipt
(Maybe MessageIdData)
(Maybe MessageIdData)
-> CommandSendReceipt -> Maybe MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'messageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'messageId") CommandSendReceipt
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: MessageIdData
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
MessageIdData
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSendReceipt
CommandSendReceipt
(Maybe Word64)
(Maybe Word64)
-> CommandSendReceipt -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'highestSequenceId") CommandSendReceipt
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandSendReceipt CommandSendReceipt FieldSet FieldSet
-> CommandSendReceipt -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandSendReceipt CommandSendReceipt FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandSendReceipt
_x)))))
instance Control.DeepSeq.NFData CommandSendReceipt where
rnf :: CommandSendReceipt -> ()
rnf
= \ x__ :: CommandSendReceipt
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendReceipt -> FieldSet
_CommandSendReceipt'_unknownFields CommandSendReceipt
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendReceipt -> Word64
_CommandSendReceipt'producerId CommandSendReceipt
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendReceipt -> Word64
_CommandSendReceipt'sequenceId CommandSendReceipt
x__)
(Maybe MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendReceipt -> Maybe MessageIdData
_CommandSendReceipt'messageId CommandSendReceipt
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSendReceipt -> Maybe Word64
_CommandSendReceipt'highestSequenceId CommandSendReceipt
x__) ()))))
data CommandSubscribe
= CommandSubscribe'_constructor {CommandSubscribe -> Text
_CommandSubscribe'topic :: !Data.Text.Text,
CommandSubscribe -> Text
_CommandSubscribe'subscription :: !Data.Text.Text,
CommandSubscribe -> CommandSubscribe'SubType
_CommandSubscribe'subType :: !CommandSubscribe'SubType,
CommandSubscribe -> Word64
_CommandSubscribe'consumerId :: !Data.Word.Word64,
CommandSubscribe -> Word64
_CommandSubscribe'requestId :: !Data.Word.Word64,
CommandSubscribe -> Maybe Text
_CommandSubscribe'consumerName :: !(Prelude.Maybe Data.Text.Text),
CommandSubscribe -> Maybe Int32
_CommandSubscribe'priorityLevel :: !(Prelude.Maybe Data.Int.Int32),
CommandSubscribe -> Maybe Bool
_CommandSubscribe'durable :: !(Prelude.Maybe Prelude.Bool),
CommandSubscribe -> Maybe MessageIdData
_CommandSubscribe'startMessageId :: !(Prelude.Maybe MessageIdData),
CommandSubscribe -> Vector KeyValue
_CommandSubscribe'metadata :: !(Data.Vector.Vector KeyValue),
CommandSubscribe -> Maybe Bool
_CommandSubscribe'readCompacted :: !(Prelude.Maybe Prelude.Bool),
CommandSubscribe -> Maybe Schema
_CommandSubscribe'schema :: !(Prelude.Maybe Schema),
CommandSubscribe -> Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition :: !(Prelude.Maybe CommandSubscribe'InitialPosition),
CommandSubscribe -> Maybe Bool
_CommandSubscribe'replicateSubscriptionState :: !(Prelude.Maybe Prelude.Bool),
CommandSubscribe -> Maybe Bool
_CommandSubscribe'forceTopicCreation :: !(Prelude.Maybe Prelude.Bool),
CommandSubscribe -> Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec :: !(Prelude.Maybe Data.Word.Word64),
CommandSubscribe -> Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta :: !(Prelude.Maybe KeySharedMeta),
CommandSubscribe -> FieldSet
_CommandSubscribe'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSubscribe -> CommandSubscribe -> Bool
(CommandSubscribe -> CommandSubscribe -> Bool)
-> (CommandSubscribe -> CommandSubscribe -> Bool)
-> Eq CommandSubscribe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSubscribe -> CommandSubscribe -> Bool
$c/= :: CommandSubscribe -> CommandSubscribe -> Bool
== :: CommandSubscribe -> CommandSubscribe -> Bool
$c== :: CommandSubscribe -> CommandSubscribe -> Bool
Prelude.Eq, Eq CommandSubscribe
Eq CommandSubscribe =>
(CommandSubscribe -> CommandSubscribe -> Ordering)
-> (CommandSubscribe -> CommandSubscribe -> Bool)
-> (CommandSubscribe -> CommandSubscribe -> Bool)
-> (CommandSubscribe -> CommandSubscribe -> Bool)
-> (CommandSubscribe -> CommandSubscribe -> Bool)
-> (CommandSubscribe -> CommandSubscribe -> CommandSubscribe)
-> (CommandSubscribe -> CommandSubscribe -> CommandSubscribe)
-> Ord CommandSubscribe
CommandSubscribe -> CommandSubscribe -> Bool
CommandSubscribe -> CommandSubscribe -> Ordering
CommandSubscribe -> CommandSubscribe -> CommandSubscribe
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSubscribe -> CommandSubscribe -> CommandSubscribe
$cmin :: CommandSubscribe -> CommandSubscribe -> CommandSubscribe
max :: CommandSubscribe -> CommandSubscribe -> CommandSubscribe
$cmax :: CommandSubscribe -> CommandSubscribe -> CommandSubscribe
>= :: CommandSubscribe -> CommandSubscribe -> Bool
$c>= :: CommandSubscribe -> CommandSubscribe -> Bool
> :: CommandSubscribe -> CommandSubscribe -> Bool
$c> :: CommandSubscribe -> CommandSubscribe -> Bool
<= :: CommandSubscribe -> CommandSubscribe -> Bool
$c<= :: CommandSubscribe -> CommandSubscribe -> Bool
< :: CommandSubscribe -> CommandSubscribe -> Bool
$c< :: CommandSubscribe -> CommandSubscribe -> Bool
compare :: CommandSubscribe -> CommandSubscribe -> Ordering
$ccompare :: CommandSubscribe -> CommandSubscribe -> Ordering
$cp1Ord :: Eq CommandSubscribe
Prelude.Ord)
instance Prelude.Show CommandSubscribe where
showsPrec :: Int -> CommandSubscribe -> ShowS
showsPrec _ __x :: CommandSubscribe
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSubscribe -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSubscribe
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSubscribe "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Text -> f Text) -> CommandSubscribe -> f CommandSubscribe)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Text)
-> (CommandSubscribe -> Text -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Text
_CommandSubscribe'topic
(\ x__ :: CommandSubscribe
x__ y__ :: Text
y__ -> CommandSubscribe
x__ {_CommandSubscribe'topic :: Text
_CommandSubscribe'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "subscription" Data.Text.Text where
fieldOf :: Proxy# "subscription"
-> (Text -> f Text) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Text -> f Text) -> CommandSubscribe -> f CommandSubscribe)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Text)
-> (CommandSubscribe -> Text -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Text
_CommandSubscribe'subscription
(\ x__ :: CommandSubscribe
x__ y__ :: Text
y__ -> CommandSubscribe
x__ {_CommandSubscribe'subscription :: Text
_CommandSubscribe'subscription = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "subType" CommandSubscribe'SubType where
fieldOf :: Proxy# "subType"
-> (CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> CommandSubscribe -> f CommandSubscribe)
-> ((CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> (CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> CommandSubscribe'SubType)
-> (CommandSubscribe
-> CommandSubscribe'SubType -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
CommandSubscribe'SubType
CommandSubscribe'SubType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> CommandSubscribe'SubType
_CommandSubscribe'subType
(\ x__ :: CommandSubscribe
x__ y__ :: CommandSubscribe'SubType
y__ -> CommandSubscribe
x__ {_CommandSubscribe'subType :: CommandSubscribe'SubType
_CommandSubscribe'subType = CommandSubscribe'SubType
y__}))
(CommandSubscribe'SubType -> f CommandSubscribe'SubType)
-> CommandSubscribe'SubType -> f CommandSubscribe'SubType
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Word64 -> f Word64) -> CommandSubscribe -> f CommandSubscribe)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Word64)
-> (CommandSubscribe -> Word64 -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Word64
_CommandSubscribe'consumerId
(\ x__ :: CommandSubscribe
x__ y__ :: Word64
y__ -> CommandSubscribe
x__ {_CommandSubscribe'consumerId :: Word64
_CommandSubscribe'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Word64 -> f Word64) -> CommandSubscribe -> f CommandSubscribe)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Word64)
-> (CommandSubscribe -> Word64 -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Word64
_CommandSubscribe'requestId
(\ x__ :: CommandSubscribe
x__ y__ :: Word64
y__ -> CommandSubscribe
x__ {_CommandSubscribe'requestId :: Word64
_CommandSubscribe'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "consumerName" Data.Text.Text where
fieldOf :: Proxy# "consumerName"
-> (Text -> f Text) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Text)
-> (CommandSubscribe -> Maybe Text -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Text
_CommandSubscribe'consumerName
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Text
y__ -> CommandSubscribe
x__ {_CommandSubscribe'consumerName :: Maybe Text
_CommandSubscribe'consumerName = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'consumerName" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'consumerName"
-> (Maybe Text -> f (Maybe Text))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Text)
-> (CommandSubscribe -> Maybe Text -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Text
_CommandSubscribe'consumerName
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Text
y__ -> CommandSubscribe
x__ {_CommandSubscribe'consumerName :: Maybe Text
_CommandSubscribe'consumerName = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "priorityLevel" Data.Int.Int32 where
fieldOf :: Proxy# "priorityLevel"
-> (Int32 -> f Int32) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Int32)
-> (CommandSubscribe -> Maybe Int32 -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Int32
_CommandSubscribe'priorityLevel
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Int32
y__ -> CommandSubscribe
x__ {_CommandSubscribe'priorityLevel :: Maybe Int32
_CommandSubscribe'priorityLevel = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'priorityLevel" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'priorityLevel"
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Int32)
-> (CommandSubscribe -> Maybe Int32 -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Int32
_CommandSubscribe'priorityLevel
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Int32
y__ -> CommandSubscribe
x__ {_CommandSubscribe'priorityLevel :: Maybe Int32
_CommandSubscribe'priorityLevel = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "durable" Prelude.Bool where
fieldOf :: Proxy# "durable"
-> (Bool -> f Bool) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'durable
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'durable :: Maybe Bool
_CommandSubscribe'durable = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.True)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'durable" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'durable"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'durable
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'durable :: Maybe Bool
_CommandSubscribe'durable = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "startMessageId" MessageIdData where
fieldOf :: Proxy# "startMessageId"
-> (MessageIdData -> f MessageIdData)
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSubscribe -> f CommandSubscribe)
-> ((MessageIdData -> f MessageIdData)
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (MessageIdData -> f MessageIdData)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe MessageIdData)
-> (CommandSubscribe -> Maybe MessageIdData -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe MessageIdData)
(Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe MessageIdData
_CommandSubscribe'startMessageId
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe MessageIdData
y__ -> CommandSubscribe
x__ {_CommandSubscribe'startMessageId :: Maybe MessageIdData
_CommandSubscribe'startMessageId = Maybe MessageIdData
y__}))
(MessageIdData -> Lens' (Maybe MessageIdData) MessageIdData
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'startMessageId" (Prelude.Maybe MessageIdData) where
fieldOf :: Proxy# "maybe'startMessageId"
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData))
-> (Maybe MessageIdData -> f (Maybe MessageIdData))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe MessageIdData)
-> (CommandSubscribe -> Maybe MessageIdData -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe MessageIdData)
(Maybe MessageIdData)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe MessageIdData
_CommandSubscribe'startMessageId
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe MessageIdData
y__ -> CommandSubscribe
x__ {_CommandSubscribe'startMessageId :: Maybe MessageIdData
_CommandSubscribe'startMessageId = Maybe MessageIdData
y__}))
(Maybe MessageIdData -> f (Maybe MessageIdData))
-> Maybe MessageIdData -> f (Maybe MessageIdData)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "metadata" [KeyValue] where
fieldOf :: Proxy# "metadata"
-> ([KeyValue] -> f [KeyValue])
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> CommandSubscribe -> f CommandSubscribe)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Vector KeyValue)
-> (CommandSubscribe -> Vector KeyValue -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Vector KeyValue)
(Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Vector KeyValue
_CommandSubscribe'metadata
(\ x__ :: CommandSubscribe
x__ y__ :: Vector KeyValue
y__ -> CommandSubscribe
x__ {_CommandSubscribe'metadata :: Vector KeyValue
_CommandSubscribe'metadata = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField CommandSubscribe "vec'metadata" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'metadata"
-> (Vector KeyValue -> f (Vector KeyValue))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Vector KeyValue)
-> (CommandSubscribe -> Vector KeyValue -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Vector KeyValue)
(Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Vector KeyValue
_CommandSubscribe'metadata
(\ x__ :: CommandSubscribe
x__ y__ :: Vector KeyValue
y__ -> CommandSubscribe
x__ {_CommandSubscribe'metadata :: Vector KeyValue
_CommandSubscribe'metadata = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "readCompacted" Prelude.Bool where
fieldOf :: Proxy# "readCompacted"
-> (Bool -> f Bool) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'readCompacted
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'readCompacted :: Maybe Bool
_CommandSubscribe'readCompacted = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'readCompacted" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'readCompacted"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'readCompacted
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'readCompacted :: Maybe Bool
_CommandSubscribe'readCompacted = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "schema" Schema where
fieldOf :: Proxy# "schema"
-> (Schema -> f Schema) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Schema -> f Schema) -> Maybe Schema -> f (Maybe Schema))
-> (Schema -> f Schema)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Schema)
-> (CommandSubscribe -> Maybe Schema -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Schema
_CommandSubscribe'schema
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Schema
y__ -> CommandSubscribe
x__ {_CommandSubscribe'schema :: Maybe Schema
_CommandSubscribe'schema = Maybe Schema
y__}))
(Schema -> Lens' (Maybe Schema) Schema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'schema" (Prelude.Maybe Schema) where
fieldOf :: Proxy# "maybe'schema"
-> (Maybe Schema -> f (Maybe Schema))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema))
-> (Maybe Schema -> f (Maybe Schema))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Schema)
-> (CommandSubscribe -> Maybe Schema -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Schema
_CommandSubscribe'schema
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Schema
y__ -> CommandSubscribe
x__ {_CommandSubscribe'schema :: Maybe Schema
_CommandSubscribe'schema = Maybe Schema
y__}))
(Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "initialPosition" CommandSubscribe'InitialPosition where
fieldOf :: Proxy# "initialPosition"
-> (CommandSubscribe'InitialPosition
-> f CommandSubscribe'InitialPosition)
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> CommandSubscribe -> f CommandSubscribe)
-> ((CommandSubscribe'InitialPosition
-> f CommandSubscribe'InitialPosition)
-> Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> (CommandSubscribe'InitialPosition
-> f CommandSubscribe'InitialPosition)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe CommandSubscribe'InitialPosition)
-> (CommandSubscribe
-> Maybe CommandSubscribe'InitialPosition -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe CommandSubscribe'InitialPosition)
(Maybe CommandSubscribe'InitialPosition)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe CommandSubscribe'InitialPosition
y__ -> CommandSubscribe
x__ {_CommandSubscribe'initialPosition :: Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition = Maybe CommandSubscribe'InitialPosition
y__}))
(CommandSubscribe'InitialPosition
-> Lens'
(Maybe CommandSubscribe'InitialPosition)
CommandSubscribe'InitialPosition
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CommandSubscribe'InitialPosition
CommandSubscribe'Latest)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'initialPosition" (Prelude.Maybe CommandSubscribe'InitialPosition) where
fieldOf :: Proxy# "maybe'initialPosition"
-> (Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> (Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe CommandSubscribe'InitialPosition)
-> (CommandSubscribe
-> Maybe CommandSubscribe'InitialPosition -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe CommandSubscribe'InitialPosition)
(Maybe CommandSubscribe'InitialPosition)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe CommandSubscribe'InitialPosition
y__ -> CommandSubscribe
x__ {_CommandSubscribe'initialPosition :: Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition = Maybe CommandSubscribe'InitialPosition
y__}))
(Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition))
-> Maybe CommandSubscribe'InitialPosition
-> f (Maybe CommandSubscribe'InitialPosition)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "replicateSubscriptionState" Prelude.Bool where
fieldOf :: Proxy# "replicateSubscriptionState"
-> (Bool -> f Bool) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'replicateSubscriptionState
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__
-> CommandSubscribe
x__ {_CommandSubscribe'replicateSubscriptionState :: Maybe Bool
_CommandSubscribe'replicateSubscriptionState = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'replicateSubscriptionState" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'replicateSubscriptionState"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'replicateSubscriptionState
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__
-> CommandSubscribe
x__ {_CommandSubscribe'replicateSubscriptionState :: Maybe Bool
_CommandSubscribe'replicateSubscriptionState = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "forceTopicCreation" Prelude.Bool where
fieldOf :: Proxy# "forceTopicCreation"
-> (Bool -> f Bool) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'forceTopicCreation
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'forceTopicCreation :: Maybe Bool
_CommandSubscribe'forceTopicCreation = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.True)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'forceTopicCreation" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'forceTopicCreation"
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Bool)
-> (CommandSubscribe -> Maybe Bool -> CommandSubscribe)
-> Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Bool
_CommandSubscribe'forceTopicCreation
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Bool
y__ -> CommandSubscribe
x__ {_CommandSubscribe'forceTopicCreation :: Maybe Bool
_CommandSubscribe'forceTopicCreation = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "startMessageRollbackDurationSec" Data.Word.Word64 where
fieldOf :: Proxy# "startMessageRollbackDurationSec"
-> (Word64 -> f Word64) -> CommandSubscribe -> f CommandSubscribe
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Word64)
-> (CommandSubscribe -> Maybe Word64 -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Word64
y__
-> CommandSubscribe
x__ {_CommandSubscribe'startMessageRollbackDurationSec :: Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'startMessageRollbackDurationSec" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'startMessageRollbackDurationSec"
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe Word64)
-> (CommandSubscribe -> Maybe Word64 -> CommandSubscribe)
-> Lens
CommandSubscribe CommandSubscribe (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe Word64
y__
-> CommandSubscribe
x__ {_CommandSubscribe'startMessageRollbackDurationSec :: Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSubscribe "keySharedMeta" KeySharedMeta where
fieldOf :: Proxy# "keySharedMeta"
-> (KeySharedMeta -> f KeySharedMeta)
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> CommandSubscribe -> f CommandSubscribe)
-> ((KeySharedMeta -> f KeySharedMeta)
-> Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> (KeySharedMeta -> f KeySharedMeta)
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe KeySharedMeta)
-> (CommandSubscribe -> Maybe KeySharedMeta -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe KeySharedMeta)
(Maybe KeySharedMeta)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe KeySharedMeta
y__ -> CommandSubscribe
x__ {_CommandSubscribe'keySharedMeta :: Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta = Maybe KeySharedMeta
y__}))
(KeySharedMeta -> Lens' (Maybe KeySharedMeta) KeySharedMeta
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens KeySharedMeta
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSubscribe "maybe'keySharedMeta" (Prelude.Maybe KeySharedMeta) where
fieldOf :: Proxy# "maybe'keySharedMeta"
-> (Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> CommandSubscribe
-> f CommandSubscribe
fieldOf _
= ((Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> CommandSubscribe -> f CommandSubscribe)
-> ((Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> (Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> CommandSubscribe
-> f CommandSubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSubscribe -> Maybe KeySharedMeta)
-> (CommandSubscribe -> Maybe KeySharedMeta -> CommandSubscribe)
-> Lens
CommandSubscribe
CommandSubscribe
(Maybe KeySharedMeta)
(Maybe KeySharedMeta)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta
(\ x__ :: CommandSubscribe
x__ y__ :: Maybe KeySharedMeta
y__ -> CommandSubscribe
x__ {_CommandSubscribe'keySharedMeta :: Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta = Maybe KeySharedMeta
y__}))
(Maybe KeySharedMeta -> f (Maybe KeySharedMeta))
-> Maybe KeySharedMeta -> f (Maybe KeySharedMeta)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSubscribe where
messageName :: Proxy CommandSubscribe -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSubscribe"
packedMessageDescriptor :: Proxy CommandSubscribe -> ByteString
packedMessageDescriptor _
= "\n\
\\DLECommandSubscribe\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\"\n\
\\fsubscription\CAN\STX \STX(\tR\fsubscription\DC2@\n\
\\asubType\CAN\ETX \STX(\SO2&.pulsar.proto.CommandSubscribe.SubTypeR\asubType\DC2\US\n\
\\vconsumer_id\CAN\EOT \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\ENQ \STX(\EOTR\trequestId\DC2#\n\
\\rconsumer_name\CAN\ACK \SOH(\tR\fconsumerName\DC2%\n\
\\SOpriority_level\CAN\a \SOH(\ENQR\rpriorityLevel\DC2\RS\n\
\\adurable\CAN\b \SOH(\b:\EOTtrueR\adurable\DC2E\n\
\\DLEstart_message_id\CAN\t \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\SOstartMessageId\DC22\n\
\\bmetadata\CAN\n\
\ \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata\DC2%\n\
\\SOread_compacted\CAN\v \SOH(\bR\rreadCompacted\DC2,\n\
\\ACKschema\CAN\f \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2`\n\
\\SIinitialPosition\CAN\r \SOH(\SO2..pulsar.proto.CommandSubscribe.InitialPosition:\ACKLatestR\SIinitialPosition\DC2@\n\
\\FSreplicate_subscription_state\CAN\SO \SOH(\bR\SUBreplicateSubscriptionState\DC26\n\
\\DC4force_topic_creation\CAN\SI \SOH(\b:\EOTtrueR\DC2forceTopicCreation\DC2O\n\
\#start_message_rollback_duration_sec\CAN\DLE \SOH(\EOT:\SOH0R\USstartMessageRollbackDurationSec\DC2A\n\
\\rkeySharedMeta\CAN\DC1 \SOH(\v2\ESC.pulsar.proto.KeySharedMetaR\rkeySharedMeta\"B\n\
\\aSubType\DC2\r\n\
\\tExclusive\DLE\NUL\DC2\n\
\\n\
\\ACKShared\DLE\SOH\DC2\f\n\
\\bFailover\DLE\STX\DC2\SO\n\
\\n\
\Key_Shared\DLE\ETX\"+\n\
\\SIInitialPosition\DC2\n\
\\n\
\\ACKLatest\DLE\NUL\DC2\f\n\
\\bEarliest\DLE\SOH"
packedFileDescriptor :: Proxy CommandSubscribe -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSubscribe)
fieldsByTag
= let
topic__field_descriptor :: FieldDescriptor CommandSubscribe
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandSubscribe Text
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandSubscribe CommandSubscribe Text Text
-> FieldAccessor CommandSubscribe Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
subscription__field_descriptor :: FieldDescriptor CommandSubscribe
subscription__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandSubscribe Text
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subscription"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens CommandSubscribe CommandSubscribe Text Text
-> FieldAccessor CommandSubscribe Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
subType__field_descriptor :: FieldDescriptor CommandSubscribe
subType__field_descriptor
= String
-> FieldTypeDescriptor CommandSubscribe'SubType
-> FieldAccessor CommandSubscribe CommandSubscribe'SubType
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subType"
(ScalarField CommandSubscribe'SubType
-> FieldTypeDescriptor CommandSubscribe'SubType
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandSubscribe'SubType
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandSubscribe'SubType)
(WireDefault CommandSubscribe'SubType
-> Lens
CommandSubscribe
CommandSubscribe
CommandSubscribe'SubType
CommandSubscribe'SubType
-> FieldAccessor CommandSubscribe CommandSubscribe'SubType
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault CommandSubscribe'SubType
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "subType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subType")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
consumerId__field_descriptor :: FieldDescriptor CommandSubscribe
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSubscribe Word64
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSubscribe CommandSubscribe Word64 Word64
-> FieldAccessor CommandSubscribe Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
requestId__field_descriptor :: FieldDescriptor CommandSubscribe
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSubscribe Word64
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSubscribe CommandSubscribe Word64 Word64
-> FieldAccessor CommandSubscribe Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
consumerName__field_descriptor :: FieldDescriptor CommandSubscribe
consumerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor CommandSubscribe Text
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens CommandSubscribe CommandSubscribe (Maybe Text) (Maybe Text)
-> FieldAccessor CommandSubscribe Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerName")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
priorityLevel__field_descriptor :: FieldDescriptor CommandSubscribe
priorityLevel__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor CommandSubscribe Int32
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"priority_level"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens CommandSubscribe CommandSubscribe (Maybe Int32) (Maybe Int32)
-> FieldAccessor CommandSubscribe Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'priorityLevel" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'priorityLevel")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
durable__field_descriptor :: FieldDescriptor CommandSubscribe
durable__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandSubscribe Bool
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"durable"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandSubscribe Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'durable" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'durable")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
startMessageId__field_descriptor :: FieldDescriptor CommandSubscribe
startMessageId__field_descriptor
= String
-> FieldTypeDescriptor MessageIdData
-> FieldAccessor CommandSubscribe MessageIdData
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"start_message_id"
(MessageOrGroup -> FieldTypeDescriptor MessageIdData
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor MessageIdData)
(Lens
CommandSubscribe
CommandSubscribe
(Maybe MessageIdData)
(Maybe MessageIdData)
-> FieldAccessor CommandSubscribe MessageIdData
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'startMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'startMessageId")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
metadata__field_descriptor :: FieldDescriptor CommandSubscribe
metadata__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor CommandSubscribe KeyValue
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"metadata"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing
-> Lens' CommandSubscribe [KeyValue]
-> FieldAccessor CommandSubscribe KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"metadata")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
readCompacted__field_descriptor :: FieldDescriptor CommandSubscribe
readCompacted__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandSubscribe Bool
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"read_compacted"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandSubscribe Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'readCompacted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'readCompacted")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
schema__field_descriptor :: FieldDescriptor CommandSubscribe
schema__field_descriptor
= String
-> FieldTypeDescriptor Schema
-> FieldAccessor CommandSubscribe Schema
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema"
(MessageOrGroup -> FieldTypeDescriptor Schema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Schema)
(Lens
CommandSubscribe CommandSubscribe (Maybe Schema) (Maybe Schema)
-> FieldAccessor CommandSubscribe Schema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
initialPosition__field_descriptor :: FieldDescriptor CommandSubscribe
initialPosition__field_descriptor
= String
-> FieldTypeDescriptor CommandSubscribe'InitialPosition
-> FieldAccessor CommandSubscribe CommandSubscribe'InitialPosition
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"initialPosition"
(ScalarField CommandSubscribe'InitialPosition
-> FieldTypeDescriptor CommandSubscribe'InitialPosition
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CommandSubscribe'InitialPosition
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CommandSubscribe'InitialPosition)
(Lens
CommandSubscribe
CommandSubscribe
(Maybe CommandSubscribe'InitialPosition)
(Maybe CommandSubscribe'InitialPosition)
-> FieldAccessor CommandSubscribe CommandSubscribe'InitialPosition
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'initialPosition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'initialPosition")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
replicateSubscriptionState__field_descriptor :: FieldDescriptor CommandSubscribe
replicateSubscriptionState__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandSubscribe Bool
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"replicate_subscription_state"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandSubscribe Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'replicateSubscriptionState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'replicateSubscriptionState")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
forceTopicCreation__field_descriptor :: FieldDescriptor CommandSubscribe
forceTopicCreation__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor CommandSubscribe Bool
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"force_topic_creation"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens CommandSubscribe CommandSubscribe (Maybe Bool) (Maybe Bool)
-> FieldAccessor CommandSubscribe Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'forceTopicCreation" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'forceTopicCreation")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
startMessageRollbackDurationSec__field_descriptor :: FieldDescriptor CommandSubscribe
startMessageRollbackDurationSec__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSubscribe Word64
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"start_message_rollback_duration_sec"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
CommandSubscribe CommandSubscribe (Maybe Word64) (Maybe Word64)
-> FieldAccessor CommandSubscribe Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'startMessageRollbackDurationSec" a,
Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'startMessageRollbackDurationSec")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
keySharedMeta__field_descriptor :: FieldDescriptor CommandSubscribe
keySharedMeta__field_descriptor
= String
-> FieldTypeDescriptor KeySharedMeta
-> FieldAccessor CommandSubscribe KeySharedMeta
-> FieldDescriptor CommandSubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"keySharedMeta"
(MessageOrGroup -> FieldTypeDescriptor KeySharedMeta
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeySharedMeta)
(Lens
CommandSubscribe
CommandSubscribe
(Maybe KeySharedMeta)
(Maybe KeySharedMeta)
-> FieldAccessor CommandSubscribe KeySharedMeta
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'keySharedMeta" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'keySharedMeta")) ::
Data.ProtoLens.FieldDescriptor CommandSubscribe
in
[(Tag, FieldDescriptor CommandSubscribe)]
-> Map Tag (FieldDescriptor CommandSubscribe)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSubscribe
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSubscribe
subscription__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor CommandSubscribe
subType__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor CommandSubscribe
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor CommandSubscribe
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor CommandSubscribe
consumerName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor CommandSubscribe
priorityLevel__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor CommandSubscribe
durable__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor CommandSubscribe
startMessageId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 10, FieldDescriptor CommandSubscribe
metadata__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 11, FieldDescriptor CommandSubscribe
readCompacted__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 12, FieldDescriptor CommandSubscribe
schema__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 13, FieldDescriptor CommandSubscribe
initialPosition__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 14,
FieldDescriptor CommandSubscribe
replicateSubscriptionState__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 15, FieldDescriptor CommandSubscribe
forceTopicCreation__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 16,
FieldDescriptor CommandSubscribe
startMessageRollbackDurationSec__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 17, FieldDescriptor CommandSubscribe
keySharedMeta__field_descriptor)]
unknownFields :: LensLike' f CommandSubscribe FieldSet
unknownFields
= (CommandSubscribe -> FieldSet)
-> (CommandSubscribe -> FieldSet -> CommandSubscribe)
-> Lens' CommandSubscribe FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSubscribe -> FieldSet
_CommandSubscribe'_unknownFields
(\ x__ :: CommandSubscribe
x__ y__ :: FieldSet
y__ -> CommandSubscribe
x__ {_CommandSubscribe'_unknownFields :: FieldSet
_CommandSubscribe'_unknownFields = FieldSet
y__})
defMessage :: CommandSubscribe
defMessage
= $WCommandSubscribe'_constructor :: Text
-> Text
-> CommandSubscribe'SubType
-> Word64
-> Word64
-> Maybe Text
-> Maybe Int32
-> Maybe Bool
-> Maybe MessageIdData
-> Vector KeyValue
-> Maybe Bool
-> Maybe Schema
-> Maybe CommandSubscribe'InitialPosition
-> Maybe Bool
-> Maybe Bool
-> Maybe Word64
-> Maybe KeySharedMeta
-> FieldSet
-> CommandSubscribe
CommandSubscribe'_constructor
{_CommandSubscribe'topic :: Text
_CommandSubscribe'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSubscribe'subscription :: Text
_CommandSubscribe'subscription = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSubscribe'subType :: CommandSubscribe'SubType
_CommandSubscribe'subType = CommandSubscribe'SubType
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSubscribe'consumerId :: Word64
_CommandSubscribe'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSubscribe'requestId :: Word64
_CommandSubscribe'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSubscribe'consumerName :: Maybe Text
_CommandSubscribe'consumerName = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'priorityLevel :: Maybe Int32
_CommandSubscribe'priorityLevel = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'durable :: Maybe Bool
_CommandSubscribe'durable = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'startMessageId :: Maybe MessageIdData
_CommandSubscribe'startMessageId = Maybe MessageIdData
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'metadata :: Vector KeyValue
_CommandSubscribe'metadata = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_CommandSubscribe'readCompacted :: Maybe Bool
_CommandSubscribe'readCompacted = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'schema :: Maybe Schema
_CommandSubscribe'schema = Maybe Schema
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'initialPosition :: Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition = Maybe CommandSubscribe'InitialPosition
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'replicateSubscriptionState :: Maybe Bool
_CommandSubscribe'replicateSubscriptionState = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'forceTopicCreation :: Maybe Bool
_CommandSubscribe'forceTopicCreation = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'startMessageRollbackDurationSec :: Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'keySharedMeta :: Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta = Maybe KeySharedMeta
forall a. Maybe a
Prelude.Nothing,
_CommandSubscribe'_unknownFields :: FieldSet
_CommandSubscribe'_unknownFields = []}
parseMessage :: Parser CommandSubscribe
parseMessage
= let
loop ::
CommandSubscribe
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Bytes.Parser CommandSubscribe
loop :: CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
x :: CommandSubscribe
x
required'consumerId :: Bool
required'consumerId
required'requestId :: Bool
required'requestId
required'subType :: Bool
required'subType
required'subscription :: Bool
required'subscription
required'topic :: Bool
required'topic
mutable'metadata :: Growing Vector RealWorld KeyValue
mutable'metadata
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector KeyValue
frozen'metadata <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata)
(let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'subType then (:) "subType" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'subscription then
(:) "subscription"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) []))))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSubscribe -> Parser CommandSubscribe
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSubscribe CommandSubscribe FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSubscribe CommandSubscribe FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
CommandSubscribe
CommandSubscribe
(Vector KeyValue)
(Vector KeyValue)
-> Vector KeyValue -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") Vector KeyValue
frozen'metadata CommandSubscribe
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Text Text
-> Text -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
Prelude.False
Growing Vector RealWorld KeyValue
mutable'metadata
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"subscription"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Text Text
-> Text -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription") Text
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
Prelude.False
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
24
-> do CommandSubscribe'SubType
y <- Parser CommandSubscribe'SubType
-> String -> Parser CommandSubscribe'SubType
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandSubscribe'SubType)
-> Parser Int -> Parser CommandSubscribe'SubType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandSubscribe'SubType
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"subType"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter
CommandSubscribe
CommandSubscribe
CommandSubscribe'SubType
CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "subType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subType") CommandSubscribe'SubType
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
Prelude.False
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
32
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Word64 Word64
-> Word64 -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandSubscribe
x)
Bool
Prelude.False
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
40
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Word64 Word64
-> Word64 -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandSubscribe
x)
Bool
required'consumerId
Bool
Prelude.False
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
50
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"consumer_name"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Text Text
-> Text -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerName") Text
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
56
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"priority_level"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Int32 Int32
-> Int32 -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "priorityLevel" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"priorityLevel") Int32
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
64
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"durable"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Bool Bool
-> Bool -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "durable" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"durable") Bool
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
74
-> do MessageIdData
y <- Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser MessageIdData -> Parser MessageIdData
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser MessageIdData
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"start_message_id"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter
CommandSubscribe CommandSubscribe MessageIdData MessageIdData
-> MessageIdData -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "startMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startMessageId") MessageIdData
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
82
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"metadata"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata KeyValue
y)
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
CommandSubscribe
x
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
v
88
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"read_compacted"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Bool Bool
-> Bool -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "readCompacted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"readCompacted") Bool
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
98
-> do Schema
y <- Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Schema -> Parser Schema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Schema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"schema"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Schema Schema
-> Schema -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") Schema
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
104
-> do CommandSubscribe'InitialPosition
y <- Parser CommandSubscribe'InitialPosition
-> String -> Parser CommandSubscribe'InitialPosition
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CommandSubscribe'InitialPosition)
-> Parser Int -> Parser CommandSubscribe'InitialPosition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CommandSubscribe'InitialPosition
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"initialPosition"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter
CommandSubscribe
CommandSubscribe
CommandSubscribe'InitialPosition
CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe
-> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "initialPosition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"initialPosition") CommandSubscribe'InitialPosition
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
112
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"replicate_subscription_state"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Bool Bool
-> Bool -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "replicateSubscriptionState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"replicateSubscriptionState") Bool
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
120
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"force_topic_creation"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Bool Bool
-> Bool -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "forceTopicCreation" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"forceTopicCreation") Bool
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
128
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
"start_message_rollback_duration_sec"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe Word64 Word64
-> Word64 -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "startMessageRollbackDurationSec" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startMessageRollbackDurationSec")
Word64
y
CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
138
-> do KeySharedMeta
y <- Parser KeySharedMeta -> String -> Parser KeySharedMeta
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeySharedMeta -> Parser KeySharedMeta
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser KeySharedMeta
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"keySharedMeta"
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter
CommandSubscribe CommandSubscribe KeySharedMeta KeySharedMeta
-> KeySharedMeta -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "keySharedMeta" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"keySharedMeta") KeySharedMeta
y CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
(Setter CommandSubscribe CommandSubscribe FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSubscribe -> CommandSubscribe
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSubscribe CommandSubscribe FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSubscribe
x)
Bool
required'consumerId
Bool
required'requestId
Bool
required'subType
Bool
required'subscription
Bool
required'topic
Growing Vector RealWorld KeyValue
mutable'metadata
in
Parser CommandSubscribe -> String -> Parser CommandSubscribe
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld KeyValue
mutable'metadata <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
CommandSubscribe
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser CommandSubscribe
loop
CommandSubscribe
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld KeyValue
mutable'metadata)
"CommandSubscribe"
buildMessage :: CommandSubscribe -> Builder
buildMessage
= \ _x :: CommandSubscribe
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandSubscribe CommandSubscribe Text Text
-> CommandSubscribe -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") CommandSubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text CommandSubscribe CommandSubscribe Text Text
-> CommandSubscribe -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription") CommandSubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Int -> Builder)
-> (CommandSubscribe'SubType -> Int)
-> CommandSubscribe'SubType
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandSubscribe'SubType -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
CommandSubscribe'SubType
CommandSubscribe
CommandSubscribe
CommandSubscribe'SubType
CommandSubscribe'SubType
-> CommandSubscribe -> CommandSubscribe'SubType
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "subType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subType") CommandSubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSubscribe CommandSubscribe Word64 Word64
-> CommandSubscribe -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandSubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSubscribe CommandSubscribe Word64 Word64
-> CommandSubscribe -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandSubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
CommandSubscribe
CommandSubscribe
(Maybe Text)
(Maybe Text)
-> CommandSubscribe -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'consumerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'consumerName") CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
CommandSubscribe
CommandSubscribe
(Maybe Int32)
(Maybe Int32)
-> CommandSubscribe -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'priorityLevel" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'priorityLevel") CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 56)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandSubscribe
CommandSubscribe
(Maybe Bool)
(Maybe Bool)
-> CommandSubscribe -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'durable" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'durable") CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe MessageIdData)
CommandSubscribe
CommandSubscribe
(Maybe MessageIdData)
(Maybe MessageIdData)
-> CommandSubscribe -> Maybe MessageIdData
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'startMessageId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'startMessageId") CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: MessageIdData
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 74)
((ByteString -> Builder)
-> (MessageIdData -> ByteString) -> MessageIdData -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
MessageIdData -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
MessageIdData
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 82)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue)
CommandSubscribe
CommandSubscribe
(Vector KeyValue)
(Vector KeyValue)
-> CommandSubscribe -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") CommandSubscribe
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandSubscribe
CommandSubscribe
(Maybe Bool)
(Maybe Bool)
-> CommandSubscribe -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'readCompacted" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'readCompacted")
CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 88)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Schema)
CommandSubscribe
CommandSubscribe
(Maybe Schema)
(Maybe Schema)
-> CommandSubscribe -> Maybe Schema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema") CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Schema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 98)
((ByteString -> Builder)
-> (Schema -> ByteString) -> Schema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Schema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Schema
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CommandSubscribe'InitialPosition)
CommandSubscribe
CommandSubscribe
(Maybe CommandSubscribe'InitialPosition)
(Maybe CommandSubscribe'InitialPosition)
-> CommandSubscribe -> Maybe CommandSubscribe'InitialPosition
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'initialPosition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'initialPosition")
CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CommandSubscribe'InitialPosition
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
104)
((Int -> Builder)
-> (CommandSubscribe'InitialPosition -> Int)
-> CommandSubscribe'InitialPosition
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CommandSubscribe'InitialPosition -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CommandSubscribe'InitialPosition
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandSubscribe
CommandSubscribe
(Maybe Bool)
(Maybe Bool)
-> CommandSubscribe -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'replicateSubscriptionState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'replicateSubscriptionState")
CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
112)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
CommandSubscribe
CommandSubscribe
(Maybe Bool)
(Maybe Bool)
-> CommandSubscribe -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'forceTopicCreation" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'forceTopicCreation")
CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
120)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
CommandSubscribe
CommandSubscribe
(Maybe Word64)
(Maybe Word64)
-> CommandSubscribe -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'startMessageRollbackDurationSec" a,
Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'startMessageRollbackDurationSec")
CommandSubscribe
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
128)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe KeySharedMeta)
CommandSubscribe
CommandSubscribe
(Maybe KeySharedMeta)
(Maybe KeySharedMeta)
-> CommandSubscribe -> Maybe KeySharedMeta
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'keySharedMeta" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'keySharedMeta")
CommandSubscribe
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: KeySharedMeta
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
138)
((ByteString -> Builder)
-> (KeySharedMeta -> ByteString) -> KeySharedMeta -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
KeySharedMeta -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeySharedMeta
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandSubscribe CommandSubscribe FieldSet FieldSet
-> CommandSubscribe -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike
FieldSet CommandSubscribe CommandSubscribe FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields
CommandSubscribe
_x))))))))))))))))))
instance Control.DeepSeq.NFData CommandSubscribe where
rnf :: CommandSubscribe -> ()
rnf
= \ x__ :: CommandSubscribe
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> FieldSet
_CommandSubscribe'_unknownFields CommandSubscribe
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Text
_CommandSubscribe'topic CommandSubscribe
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Text
_CommandSubscribe'subscription CommandSubscribe
x__)
(CommandSubscribe'SubType -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> CommandSubscribe'SubType
_CommandSubscribe'subType CommandSubscribe
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Word64
_CommandSubscribe'consumerId CommandSubscribe
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Word64
_CommandSubscribe'requestId CommandSubscribe
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Text
_CommandSubscribe'consumerName CommandSubscribe
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Int32
_CommandSubscribe'priorityLevel CommandSubscribe
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Bool
_CommandSubscribe'durable CommandSubscribe
x__)
(Maybe MessageIdData -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe MessageIdData
_CommandSubscribe'startMessageId CommandSubscribe
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Vector KeyValue
_CommandSubscribe'metadata CommandSubscribe
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Bool
_CommandSubscribe'readCompacted CommandSubscribe
x__)
(Maybe Schema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Schema
_CommandSubscribe'schema CommandSubscribe
x__)
(Maybe CommandSubscribe'InitialPosition -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe CommandSubscribe'InitialPosition
_CommandSubscribe'initialPosition CommandSubscribe
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Bool
_CommandSubscribe'replicateSubscriptionState
CommandSubscribe
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Bool
_CommandSubscribe'forceTopicCreation CommandSubscribe
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe Word64
_CommandSubscribe'startMessageRollbackDurationSec
CommandSubscribe
x__)
(Maybe KeySharedMeta -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSubscribe -> Maybe KeySharedMeta
_CommandSubscribe'keySharedMeta
CommandSubscribe
x__)
())))))))))))))))))
data CommandSubscribe'InitialPosition
= CommandSubscribe'Latest | CommandSubscribe'Earliest
deriving stock (Int -> CommandSubscribe'InitialPosition -> ShowS
[CommandSubscribe'InitialPosition] -> ShowS
CommandSubscribe'InitialPosition -> String
(Int -> CommandSubscribe'InitialPosition -> ShowS)
-> (CommandSubscribe'InitialPosition -> String)
-> ([CommandSubscribe'InitialPosition] -> ShowS)
-> Show CommandSubscribe'InitialPosition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandSubscribe'InitialPosition] -> ShowS
$cshowList :: [CommandSubscribe'InitialPosition] -> ShowS
show :: CommandSubscribe'InitialPosition -> String
$cshow :: CommandSubscribe'InitialPosition -> String
showsPrec :: Int -> CommandSubscribe'InitialPosition -> ShowS
$cshowsPrec :: Int -> CommandSubscribe'InitialPosition -> ShowS
Prelude.Show, CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
(CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> Eq CommandSubscribe'InitialPosition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c/= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
== :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c== :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
Prelude.Eq, Eq CommandSubscribe'InitialPosition
Eq CommandSubscribe'InitialPosition =>
(CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Ordering)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition)
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition)
-> Ord CommandSubscribe'InitialPosition
CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Ordering
CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
$cmin :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
max :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
$cmax :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
>= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c>= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
> :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c> :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
<= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c<= :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
< :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
$c< :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Bool
compare :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Ordering
$ccompare :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition -> Ordering
$cp1Ord :: Eq CommandSubscribe'InitialPosition
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandSubscribe'InitialPosition where
maybeToEnum :: Int -> Maybe CommandSubscribe'InitialPosition
maybeToEnum 0 = CommandSubscribe'InitialPosition
-> Maybe CommandSubscribe'InitialPosition
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'InitialPosition
CommandSubscribe'Latest
maybeToEnum 1 = CommandSubscribe'InitialPosition
-> Maybe CommandSubscribe'InitialPosition
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'InitialPosition
CommandSubscribe'Earliest
maybeToEnum _ = Maybe CommandSubscribe'InitialPosition
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandSubscribe'InitialPosition -> String
showEnum CommandSubscribe'Latest = "Latest"
showEnum CommandSubscribe'Earliest = "Earliest"
readEnum :: String -> Maybe CommandSubscribe'InitialPosition
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Latest" = CommandSubscribe'InitialPosition
-> Maybe CommandSubscribe'InitialPosition
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'InitialPosition
CommandSubscribe'Latest
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Earliest"
= CommandSubscribe'InitialPosition
-> Maybe CommandSubscribe'InitialPosition
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'InitialPosition
CommandSubscribe'Earliest
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandSubscribe'InitialPosition)
-> Maybe CommandSubscribe'InitialPosition
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandSubscribe'InitialPosition
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandSubscribe'InitialPosition where
minBound :: CommandSubscribe'InitialPosition
minBound = CommandSubscribe'InitialPosition
CommandSubscribe'Latest
maxBound :: CommandSubscribe'InitialPosition
maxBound = CommandSubscribe'InitialPosition
CommandSubscribe'Earliest
instance Prelude.Enum CommandSubscribe'InitialPosition where
toEnum :: Int -> CommandSubscribe'InitialPosition
toEnum k__ :: Int
k__
= CommandSubscribe'InitialPosition
-> (CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition)
-> Maybe CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandSubscribe'InitialPosition
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum InitialPosition: "
(Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
forall a. a -> a
Prelude.id
(Int -> Maybe CommandSubscribe'InitialPosition
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandSubscribe'InitialPosition -> Int
fromEnum CommandSubscribe'Latest = 0
fromEnum CommandSubscribe'Earliest = 1
succ :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
succ CommandSubscribe'Earliest
= String -> CommandSubscribe'InitialPosition
forall a. HasCallStack => String -> a
Prelude.error
"CommandSubscribe'InitialPosition.succ: bad argument CommandSubscribe'Earliest. This value would be out of bounds."
succ CommandSubscribe'Latest = CommandSubscribe'InitialPosition
CommandSubscribe'Earliest
pred :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
pred CommandSubscribe'Latest
= String -> CommandSubscribe'InitialPosition
forall a. HasCallStack => String -> a
Prelude.error
"CommandSubscribe'InitialPosition.pred: bad argument CommandSubscribe'Latest. This value would be out of bounds."
pred CommandSubscribe'Earliest = CommandSubscribe'InitialPosition
CommandSubscribe'Latest
enumFrom :: CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
enumFrom = CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
enumFromTo = CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
enumFromThen = CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
enumFromThenTo = CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> CommandSubscribe'InitialPosition
-> [CommandSubscribe'InitialPosition]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandSubscribe'InitialPosition where
fieldDefault :: CommandSubscribe'InitialPosition
fieldDefault = CommandSubscribe'InitialPosition
CommandSubscribe'Latest
instance Control.DeepSeq.NFData CommandSubscribe'InitialPosition where
rnf :: CommandSubscribe'InitialPosition -> ()
rnf x__ :: CommandSubscribe'InitialPosition
x__ = CommandSubscribe'InitialPosition -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandSubscribe'InitialPosition
x__ ()
data CommandSubscribe'SubType
= CommandSubscribe'Exclusive |
CommandSubscribe'Shared |
CommandSubscribe'Failover |
CommandSubscribe'Key_Shared
deriving stock (Int -> CommandSubscribe'SubType -> ShowS
[CommandSubscribe'SubType] -> ShowS
CommandSubscribe'SubType -> String
(Int -> CommandSubscribe'SubType -> ShowS)
-> (CommandSubscribe'SubType -> String)
-> ([CommandSubscribe'SubType] -> ShowS)
-> Show CommandSubscribe'SubType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandSubscribe'SubType] -> ShowS
$cshowList :: [CommandSubscribe'SubType] -> ShowS
show :: CommandSubscribe'SubType -> String
$cshow :: CommandSubscribe'SubType -> String
showsPrec :: Int -> CommandSubscribe'SubType -> ShowS
$cshowsPrec :: Int -> CommandSubscribe'SubType -> ShowS
Prelude.Show, CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
(CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> Eq CommandSubscribe'SubType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c/= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
== :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c== :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
Prelude.Eq, Eq CommandSubscribe'SubType
Eq CommandSubscribe'SubType =>
(CommandSubscribe'SubType -> CommandSubscribe'SubType -> Ordering)
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool)
-> (CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType)
-> (CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType)
-> Ord CommandSubscribe'SubType
CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
CommandSubscribe'SubType -> CommandSubscribe'SubType -> Ordering
CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType
$cmin :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType
max :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType
$cmax :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe'SubType
>= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c>= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
> :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c> :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
<= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c<= :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
< :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
$c< :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Bool
compare :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Ordering
$ccompare :: CommandSubscribe'SubType -> CommandSubscribe'SubType -> Ordering
$cp1Ord :: Eq CommandSubscribe'SubType
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CommandSubscribe'SubType where
maybeToEnum :: Int -> Maybe CommandSubscribe'SubType
maybeToEnum 0 = CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Exclusive
maybeToEnum 1 = CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Shared
maybeToEnum 2 = CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Failover
maybeToEnum 3 = CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Key_Shared
maybeToEnum _ = Maybe CommandSubscribe'SubType
forall a. Maybe a
Prelude.Nothing
showEnum :: CommandSubscribe'SubType -> String
showEnum CommandSubscribe'Exclusive = "Exclusive"
showEnum CommandSubscribe'Shared = "Shared"
showEnum CommandSubscribe'Failover = "Failover"
showEnum CommandSubscribe'Key_Shared = "Key_Shared"
readEnum :: String -> Maybe CommandSubscribe'SubType
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Exclusive"
= CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Exclusive
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Shared" = CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Shared
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Failover"
= CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Failover
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Key_Shared"
= CommandSubscribe'SubType -> Maybe CommandSubscribe'SubType
forall a. a -> Maybe a
Prelude.Just CommandSubscribe'SubType
CommandSubscribe'Key_Shared
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CommandSubscribe'SubType)
-> Maybe CommandSubscribe'SubType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CommandSubscribe'SubType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CommandSubscribe'SubType where
minBound :: CommandSubscribe'SubType
minBound = CommandSubscribe'SubType
CommandSubscribe'Exclusive
maxBound :: CommandSubscribe'SubType
maxBound = CommandSubscribe'SubType
CommandSubscribe'Key_Shared
instance Prelude.Enum CommandSubscribe'SubType where
toEnum :: Int -> CommandSubscribe'SubType
toEnum k__ :: Int
k__
= CommandSubscribe'SubType
-> (CommandSubscribe'SubType -> CommandSubscribe'SubType)
-> Maybe CommandSubscribe'SubType
-> CommandSubscribe'SubType
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CommandSubscribe'SubType
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum SubType: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CommandSubscribe'SubType -> CommandSubscribe'SubType
forall a. a -> a
Prelude.id
(Int -> Maybe CommandSubscribe'SubType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CommandSubscribe'SubType -> Int
fromEnum CommandSubscribe'Exclusive = 0
fromEnum CommandSubscribe'Shared = 1
fromEnum CommandSubscribe'Failover = 2
fromEnum CommandSubscribe'Key_Shared = 3
succ :: CommandSubscribe'SubType -> CommandSubscribe'SubType
succ CommandSubscribe'Key_Shared
= String -> CommandSubscribe'SubType
forall a. HasCallStack => String -> a
Prelude.error
"CommandSubscribe'SubType.succ: bad argument CommandSubscribe'Key_Shared. This value would be out of bounds."
succ CommandSubscribe'Exclusive = CommandSubscribe'SubType
CommandSubscribe'Shared
succ CommandSubscribe'Shared = CommandSubscribe'SubType
CommandSubscribe'Failover
succ CommandSubscribe'Failover = CommandSubscribe'SubType
CommandSubscribe'Key_Shared
pred :: CommandSubscribe'SubType -> CommandSubscribe'SubType
pred CommandSubscribe'Exclusive
= String -> CommandSubscribe'SubType
forall a. HasCallStack => String -> a
Prelude.error
"CommandSubscribe'SubType.pred: bad argument CommandSubscribe'Exclusive. This value would be out of bounds."
pred CommandSubscribe'Shared = CommandSubscribe'SubType
CommandSubscribe'Exclusive
pred CommandSubscribe'Failover = CommandSubscribe'SubType
CommandSubscribe'Shared
pred CommandSubscribe'Key_Shared = CommandSubscribe'SubType
CommandSubscribe'Failover
enumFrom :: CommandSubscribe'SubType -> [CommandSubscribe'SubType]
enumFrom = CommandSubscribe'SubType -> [CommandSubscribe'SubType]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> [CommandSubscribe'SubType]
enumFromTo = CommandSubscribe'SubType
-> CommandSubscribe'SubType -> [CommandSubscribe'SubType]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CommandSubscribe'SubType
-> CommandSubscribe'SubType -> [CommandSubscribe'SubType]
enumFromThen = CommandSubscribe'SubType
-> CommandSubscribe'SubType -> [CommandSubscribe'SubType]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CommandSubscribe'SubType
-> CommandSubscribe'SubType
-> CommandSubscribe'SubType
-> [CommandSubscribe'SubType]
enumFromThenTo = CommandSubscribe'SubType
-> CommandSubscribe'SubType
-> CommandSubscribe'SubType
-> [CommandSubscribe'SubType]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CommandSubscribe'SubType where
fieldDefault :: CommandSubscribe'SubType
fieldDefault = CommandSubscribe'SubType
CommandSubscribe'Exclusive
instance Control.DeepSeq.NFData CommandSubscribe'SubType where
rnf :: CommandSubscribe'SubType -> ()
rnf x__ :: CommandSubscribe'SubType
x__ = CommandSubscribe'SubType -> () -> ()
forall a b. a -> b -> b
Prelude.seq CommandSubscribe'SubType
x__ ()
data CommandSuccess
= CommandSuccess'_constructor {CommandSuccess -> Word64
_CommandSuccess'requestId :: !Data.Word.Word64,
CommandSuccess -> Maybe Schema
_CommandSuccess'schema :: !(Prelude.Maybe Schema),
CommandSuccess -> FieldSet
_CommandSuccess'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandSuccess -> CommandSuccess -> Bool
(CommandSuccess -> CommandSuccess -> Bool)
-> (CommandSuccess -> CommandSuccess -> Bool) -> Eq CommandSuccess
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandSuccess -> CommandSuccess -> Bool
$c/= :: CommandSuccess -> CommandSuccess -> Bool
== :: CommandSuccess -> CommandSuccess -> Bool
$c== :: CommandSuccess -> CommandSuccess -> Bool
Prelude.Eq, Eq CommandSuccess
Eq CommandSuccess =>
(CommandSuccess -> CommandSuccess -> Ordering)
-> (CommandSuccess -> CommandSuccess -> Bool)
-> (CommandSuccess -> CommandSuccess -> Bool)
-> (CommandSuccess -> CommandSuccess -> Bool)
-> (CommandSuccess -> CommandSuccess -> Bool)
-> (CommandSuccess -> CommandSuccess -> CommandSuccess)
-> (CommandSuccess -> CommandSuccess -> CommandSuccess)
-> Ord CommandSuccess
CommandSuccess -> CommandSuccess -> Bool
CommandSuccess -> CommandSuccess -> Ordering
CommandSuccess -> CommandSuccess -> CommandSuccess
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandSuccess -> CommandSuccess -> CommandSuccess
$cmin :: CommandSuccess -> CommandSuccess -> CommandSuccess
max :: CommandSuccess -> CommandSuccess -> CommandSuccess
$cmax :: CommandSuccess -> CommandSuccess -> CommandSuccess
>= :: CommandSuccess -> CommandSuccess -> Bool
$c>= :: CommandSuccess -> CommandSuccess -> Bool
> :: CommandSuccess -> CommandSuccess -> Bool
$c> :: CommandSuccess -> CommandSuccess -> Bool
<= :: CommandSuccess -> CommandSuccess -> Bool
$c<= :: CommandSuccess -> CommandSuccess -> Bool
< :: CommandSuccess -> CommandSuccess -> Bool
$c< :: CommandSuccess -> CommandSuccess -> Bool
compare :: CommandSuccess -> CommandSuccess -> Ordering
$ccompare :: CommandSuccess -> CommandSuccess -> Ordering
$cp1Ord :: Eq CommandSuccess
Prelude.Ord)
instance Prelude.Show CommandSuccess where
showsPrec :: Int -> CommandSuccess -> ShowS
showsPrec _ __x :: CommandSuccess
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandSuccess -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandSuccess
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandSuccess "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64) -> CommandSuccess -> f CommandSuccess
fieldOf _
= ((Word64 -> f Word64) -> CommandSuccess -> f CommandSuccess)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandSuccess
-> f CommandSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSuccess -> Word64)
-> (CommandSuccess -> Word64 -> CommandSuccess)
-> Lens CommandSuccess CommandSuccess Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSuccess -> Word64
_CommandSuccess'requestId
(\ x__ :: CommandSuccess
x__ y__ :: Word64
y__ -> CommandSuccess
x__ {_CommandSuccess'requestId :: Word64
_CommandSuccess'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandSuccess "schema" Schema where
fieldOf :: Proxy# "schema"
-> (Schema -> f Schema) -> CommandSuccess -> f CommandSuccess
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandSuccess -> f CommandSuccess)
-> ((Schema -> f Schema) -> Maybe Schema -> f (Maybe Schema))
-> (Schema -> f Schema)
-> CommandSuccess
-> f CommandSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSuccess -> Maybe Schema)
-> (CommandSuccess -> Maybe Schema -> CommandSuccess)
-> Lens CommandSuccess CommandSuccess (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSuccess -> Maybe Schema
_CommandSuccess'schema
(\ x__ :: CommandSuccess
x__ y__ :: Maybe Schema
y__ -> CommandSuccess
x__ {_CommandSuccess'schema :: Maybe Schema
_CommandSuccess'schema = Maybe Schema
y__}))
(Schema -> Lens' (Maybe Schema) Schema
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField CommandSuccess "maybe'schema" (Prelude.Maybe Schema) where
fieldOf :: Proxy# "maybe'schema"
-> (Maybe Schema -> f (Maybe Schema))
-> CommandSuccess
-> f CommandSuccess
fieldOf _
= ((Maybe Schema -> f (Maybe Schema))
-> CommandSuccess -> f CommandSuccess)
-> ((Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema))
-> (Maybe Schema -> f (Maybe Schema))
-> CommandSuccess
-> f CommandSuccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandSuccess -> Maybe Schema)
-> (CommandSuccess -> Maybe Schema -> CommandSuccess)
-> Lens CommandSuccess CommandSuccess (Maybe Schema) (Maybe Schema)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSuccess -> Maybe Schema
_CommandSuccess'schema
(\ x__ :: CommandSuccess
x__ y__ :: Maybe Schema
y__ -> CommandSuccess
x__ {_CommandSuccess'schema :: Maybe Schema
_CommandSuccess'schema = Maybe Schema
y__}))
(Maybe Schema -> f (Maybe Schema))
-> Maybe Schema -> f (Maybe Schema)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandSuccess where
messageName :: Proxy CommandSuccess -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandSuccess"
packedMessageDescriptor :: Proxy CommandSuccess -> ByteString
packedMessageDescriptor _
= "\n\
\\SOCommandSuccess\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2,\n\
\\ACKschema\CAN\STX \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema"
packedFileDescriptor :: Proxy CommandSuccess -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandSuccess)
fieldsByTag
= let
requestId__field_descriptor :: FieldDescriptor CommandSuccess
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandSuccess Word64
-> FieldDescriptor CommandSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandSuccess CommandSuccess Word64 Word64
-> FieldAccessor CommandSuccess Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandSuccess
schema__field_descriptor :: FieldDescriptor CommandSuccess
schema__field_descriptor
= String
-> FieldTypeDescriptor Schema
-> FieldAccessor CommandSuccess Schema
-> FieldDescriptor CommandSuccess
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema"
(MessageOrGroup -> FieldTypeDescriptor Schema
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Schema)
(Lens CommandSuccess CommandSuccess (Maybe Schema) (Maybe Schema)
-> FieldAccessor CommandSuccess Schema
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema")) ::
Data.ProtoLens.FieldDescriptor CommandSuccess
in
[(Tag, FieldDescriptor CommandSuccess)]
-> Map Tag (FieldDescriptor CommandSuccess)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandSuccess
requestId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandSuccess
schema__field_descriptor)]
unknownFields :: LensLike' f CommandSuccess FieldSet
unknownFields
= (CommandSuccess -> FieldSet)
-> (CommandSuccess -> FieldSet -> CommandSuccess)
-> Lens' CommandSuccess FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandSuccess -> FieldSet
_CommandSuccess'_unknownFields
(\ x__ :: CommandSuccess
x__ y__ :: FieldSet
y__ -> CommandSuccess
x__ {_CommandSuccess'_unknownFields :: FieldSet
_CommandSuccess'_unknownFields = FieldSet
y__})
defMessage :: CommandSuccess
defMessage
= $WCommandSuccess'_constructor :: Word64 -> Maybe Schema -> FieldSet -> CommandSuccess
CommandSuccess'_constructor
{_CommandSuccess'requestId :: Word64
_CommandSuccess'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandSuccess'schema :: Maybe Schema
_CommandSuccess'schema = Maybe Schema
forall a. Maybe a
Prelude.Nothing,
_CommandSuccess'_unknownFields :: FieldSet
_CommandSuccess'_unknownFields = []}
parseMessage :: Parser CommandSuccess
parseMessage
= let
loop ::
CommandSuccess
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandSuccess
loop :: CommandSuccess -> Bool -> Parser CommandSuccess
loop x :: CommandSuccess
x required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) []
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandSuccess -> Parser CommandSuccess
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandSuccess CommandSuccess FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSuccess -> CommandSuccess
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSuccess CommandSuccess FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandSuccess
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandSuccess -> Bool -> Parser CommandSuccess
loop
(Setter CommandSuccess CommandSuccess Word64 Word64
-> Word64 -> CommandSuccess -> CommandSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandSuccess
x)
Bool
Prelude.False
18
-> do Schema
y <- Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Schema -> Parser Schema
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Schema
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"schema"
CommandSuccess -> Bool -> Parser CommandSuccess
loop
(Setter CommandSuccess CommandSuccess Schema Schema
-> Schema -> CommandSuccess -> CommandSuccess
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schema") Schema
y CommandSuccess
x)
Bool
required'requestId
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandSuccess -> Bool -> Parser CommandSuccess
loop
(Setter CommandSuccess CommandSuccess FieldSet FieldSet
-> (FieldSet -> FieldSet) -> CommandSuccess -> CommandSuccess
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandSuccess CommandSuccess FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandSuccess
x)
Bool
required'requestId
in
Parser CommandSuccess -> String -> Parser CommandSuccess
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandSuccess -> Bool -> Parser CommandSuccess
loop CommandSuccess
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True) "CommandSuccess"
buildMessage :: CommandSuccess -> Builder
buildMessage
= \ _x :: CommandSuccess
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandSuccess CommandSuccess Word64 Word64
-> CommandSuccess -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandSuccess
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Schema)
CommandSuccess
CommandSuccess
(Maybe Schema)
(Maybe Schema)
-> CommandSuccess -> Maybe Schema
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'schema" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schema") CommandSuccess
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Schema
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder)
-> (Schema -> ByteString) -> Schema -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Schema -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
Schema
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet CommandSuccess CommandSuccess FieldSet FieldSet
-> CommandSuccess -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet CommandSuccess CommandSuccess FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandSuccess
_x)))
instance Control.DeepSeq.NFData CommandSuccess where
rnf :: CommandSuccess -> ()
rnf
= \ x__ :: CommandSuccess
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSuccess -> FieldSet
_CommandSuccess'_unknownFields CommandSuccess
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandSuccess -> Word64
_CommandSuccess'requestId CommandSuccess
x__)
(Maybe Schema -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandSuccess -> Maybe Schema
_CommandSuccess'schema CommandSuccess
x__) ()))
data CommandUnsubscribe
= CommandUnsubscribe'_constructor {CommandUnsubscribe -> Word64
_CommandUnsubscribe'consumerId :: !Data.Word.Word64,
CommandUnsubscribe -> Word64
_CommandUnsubscribe'requestId :: !Data.Word.Word64,
CommandUnsubscribe -> FieldSet
_CommandUnsubscribe'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (CommandUnsubscribe -> CommandUnsubscribe -> Bool
(CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> (CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> Eq CommandUnsubscribe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c/= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
== :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c== :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
Prelude.Eq, Eq CommandUnsubscribe
Eq CommandUnsubscribe =>
(CommandUnsubscribe -> CommandUnsubscribe -> Ordering)
-> (CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> (CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> (CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> (CommandUnsubscribe -> CommandUnsubscribe -> Bool)
-> (CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe)
-> (CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe)
-> Ord CommandUnsubscribe
CommandUnsubscribe -> CommandUnsubscribe -> Bool
CommandUnsubscribe -> CommandUnsubscribe -> Ordering
CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe
$cmin :: CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe
max :: CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe
$cmax :: CommandUnsubscribe -> CommandUnsubscribe -> CommandUnsubscribe
>= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c>= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
> :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c> :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
<= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c<= :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
< :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
$c< :: CommandUnsubscribe -> CommandUnsubscribe -> Bool
compare :: CommandUnsubscribe -> CommandUnsubscribe -> Ordering
$ccompare :: CommandUnsubscribe -> CommandUnsubscribe -> Ordering
$cp1Ord :: Eq CommandUnsubscribe
Prelude.Ord)
instance Prelude.Show CommandUnsubscribe where
showsPrec :: Int -> CommandUnsubscribe -> ShowS
showsPrec _ __x :: CommandUnsubscribe
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(CommandUnsubscribe -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort CommandUnsubscribe
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField CommandUnsubscribe "consumerId" Data.Word.Word64 where
fieldOf :: Proxy# "consumerId"
-> (Word64 -> f Word64)
-> CommandUnsubscribe
-> f CommandUnsubscribe
fieldOf _
= ((Word64 -> f Word64)
-> CommandUnsubscribe -> f CommandUnsubscribe)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandUnsubscribe
-> f CommandUnsubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandUnsubscribe -> Word64)
-> (CommandUnsubscribe -> Word64 -> CommandUnsubscribe)
-> Lens CommandUnsubscribe CommandUnsubscribe Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandUnsubscribe -> Word64
_CommandUnsubscribe'consumerId
(\ x__ :: CommandUnsubscribe
x__ y__ :: Word64
y__ -> CommandUnsubscribe
x__ {_CommandUnsubscribe'consumerId :: Word64
_CommandUnsubscribe'consumerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField CommandUnsubscribe "requestId" Data.Word.Word64 where
fieldOf :: Proxy# "requestId"
-> (Word64 -> f Word64)
-> CommandUnsubscribe
-> f CommandUnsubscribe
fieldOf _
= ((Word64 -> f Word64)
-> CommandUnsubscribe -> f CommandUnsubscribe)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> CommandUnsubscribe
-> f CommandUnsubscribe
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((CommandUnsubscribe -> Word64)
-> (CommandUnsubscribe -> Word64 -> CommandUnsubscribe)
-> Lens CommandUnsubscribe CommandUnsubscribe Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandUnsubscribe -> Word64
_CommandUnsubscribe'requestId
(\ x__ :: CommandUnsubscribe
x__ y__ :: Word64
y__ -> CommandUnsubscribe
x__ {_CommandUnsubscribe'requestId :: Word64
_CommandUnsubscribe'requestId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message CommandUnsubscribe where
messageName :: Proxy CommandUnsubscribe -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.CommandUnsubscribe"
packedMessageDescriptor :: Proxy CommandUnsubscribe -> ByteString
packedMessageDescriptor _
= "\n\
\\DC2CommandUnsubscribe\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId"
packedFileDescriptor :: Proxy CommandUnsubscribe -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor CommandUnsubscribe)
fieldsByTag
= let
consumerId__field_descriptor :: FieldDescriptor CommandUnsubscribe
consumerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandUnsubscribe Word64
-> FieldDescriptor CommandUnsubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"consumer_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> FieldAccessor CommandUnsubscribe Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId")) ::
Data.ProtoLens.FieldDescriptor CommandUnsubscribe
requestId__field_descriptor :: FieldDescriptor CommandUnsubscribe
requestId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor CommandUnsubscribe Word64
-> FieldDescriptor CommandUnsubscribe
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"request_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> FieldAccessor CommandUnsubscribe Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId")) ::
Data.ProtoLens.FieldDescriptor CommandUnsubscribe
in
[(Tag, FieldDescriptor CommandUnsubscribe)]
-> Map Tag (FieldDescriptor CommandUnsubscribe)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor CommandUnsubscribe
consumerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor CommandUnsubscribe
requestId__field_descriptor)]
unknownFields :: LensLike' f CommandUnsubscribe FieldSet
unknownFields
= (CommandUnsubscribe -> FieldSet)
-> (CommandUnsubscribe -> FieldSet -> CommandUnsubscribe)
-> Lens' CommandUnsubscribe FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
CommandUnsubscribe -> FieldSet
_CommandUnsubscribe'_unknownFields
(\ x__ :: CommandUnsubscribe
x__ y__ :: FieldSet
y__ -> CommandUnsubscribe
x__ {_CommandUnsubscribe'_unknownFields :: FieldSet
_CommandUnsubscribe'_unknownFields = FieldSet
y__})
defMessage :: CommandUnsubscribe
defMessage
= $WCommandUnsubscribe'_constructor :: Word64 -> Word64 -> FieldSet -> CommandUnsubscribe
CommandUnsubscribe'_constructor
{_CommandUnsubscribe'consumerId :: Word64
_CommandUnsubscribe'consumerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandUnsubscribe'requestId :: Word64
_CommandUnsubscribe'requestId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_CommandUnsubscribe'_unknownFields :: FieldSet
_CommandUnsubscribe'_unknownFields = []}
parseMessage :: Parser CommandUnsubscribe
parseMessage
= let
loop ::
CommandUnsubscribe
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser CommandUnsubscribe
loop :: CommandUnsubscribe -> Bool -> Bool -> Parser CommandUnsubscribe
loop x :: CommandUnsubscribe
x required'consumerId :: Bool
required'consumerId required'requestId :: Bool
required'requestId
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'consumerId then (:) "consumer_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'requestId then (:) "request_id" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
CommandUnsubscribe -> Parser CommandUnsubscribe
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandUnsubscribe
-> CommandUnsubscribe
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) CommandUnsubscribe
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "consumer_id"
CommandUnsubscribe -> Bool -> Bool -> Parser CommandUnsubscribe
loop
(Setter CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> Word64 -> CommandUnsubscribe -> CommandUnsubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") Word64
y CommandUnsubscribe
x)
Bool
Prelude.False
Bool
required'requestId
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "request_id"
CommandUnsubscribe -> Bool -> Bool -> Parser CommandUnsubscribe
loop
(Setter CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> Word64 -> CommandUnsubscribe -> CommandUnsubscribe
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") Word64
y CommandUnsubscribe
x)
Bool
required'consumerId
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
CommandUnsubscribe -> Bool -> Bool -> Parser CommandUnsubscribe
loop
(Setter CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> CommandUnsubscribe
-> CommandUnsubscribe
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) CommandUnsubscribe
x)
Bool
required'consumerId
Bool
required'requestId
in
Parser CommandUnsubscribe -> String -> Parser CommandUnsubscribe
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do CommandUnsubscribe -> Bool -> Bool -> Parser CommandUnsubscribe
loop CommandUnsubscribe
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"CommandUnsubscribe"
buildMessage :: CommandUnsubscribe -> Builder
buildMessage
= \ _x :: CommandUnsubscribe
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> CommandUnsubscribe -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "consumerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"consumerId") CommandUnsubscribe
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 CommandUnsubscribe CommandUnsubscribe Word64 Word64
-> CommandUnsubscribe -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "requestId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"requestId") CommandUnsubscribe
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
-> CommandUnsubscribe -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet CommandUnsubscribe CommandUnsubscribe FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields CommandUnsubscribe
_x)))
instance Control.DeepSeq.NFData CommandUnsubscribe where
rnf :: CommandUnsubscribe -> ()
rnf
= \ x__ :: CommandUnsubscribe
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandUnsubscribe -> FieldSet
_CommandUnsubscribe'_unknownFields CommandUnsubscribe
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(CommandUnsubscribe -> Word64
_CommandUnsubscribe'consumerId CommandUnsubscribe
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (CommandUnsubscribe -> Word64
_CommandUnsubscribe'requestId CommandUnsubscribe
x__) ()))
data CompressionType
= NONE | LZ4 | ZLIB | ZSTD | SNAPPY
deriving stock (Int -> CompressionType -> ShowS
[CompressionType] -> ShowS
CompressionType -> String
(Int -> CompressionType -> ShowS)
-> (CompressionType -> String)
-> ([CompressionType] -> ShowS)
-> Show CompressionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompressionType] -> ShowS
$cshowList :: [CompressionType] -> ShowS
show :: CompressionType -> String
$cshow :: CompressionType -> String
showsPrec :: Int -> CompressionType -> ShowS
$cshowsPrec :: Int -> CompressionType -> ShowS
Prelude.Show, CompressionType -> CompressionType -> Bool
(CompressionType -> CompressionType -> Bool)
-> (CompressionType -> CompressionType -> Bool)
-> Eq CompressionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompressionType -> CompressionType -> Bool
$c/= :: CompressionType -> CompressionType -> Bool
== :: CompressionType -> CompressionType -> Bool
$c== :: CompressionType -> CompressionType -> Bool
Prelude.Eq, Eq CompressionType
Eq CompressionType =>
(CompressionType -> CompressionType -> Ordering)
-> (CompressionType -> CompressionType -> Bool)
-> (CompressionType -> CompressionType -> Bool)
-> (CompressionType -> CompressionType -> Bool)
-> (CompressionType -> CompressionType -> Bool)
-> (CompressionType -> CompressionType -> CompressionType)
-> (CompressionType -> CompressionType -> CompressionType)
-> Ord CompressionType
CompressionType -> CompressionType -> Bool
CompressionType -> CompressionType -> Ordering
CompressionType -> CompressionType -> CompressionType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompressionType -> CompressionType -> CompressionType
$cmin :: CompressionType -> CompressionType -> CompressionType
max :: CompressionType -> CompressionType -> CompressionType
$cmax :: CompressionType -> CompressionType -> CompressionType
>= :: CompressionType -> CompressionType -> Bool
$c>= :: CompressionType -> CompressionType -> Bool
> :: CompressionType -> CompressionType -> Bool
$c> :: CompressionType -> CompressionType -> Bool
<= :: CompressionType -> CompressionType -> Bool
$c<= :: CompressionType -> CompressionType -> Bool
< :: CompressionType -> CompressionType -> Bool
$c< :: CompressionType -> CompressionType -> Bool
compare :: CompressionType -> CompressionType -> Ordering
$ccompare :: CompressionType -> CompressionType -> Ordering
$cp1Ord :: Eq CompressionType
Prelude.Ord)
instance Data.ProtoLens.MessageEnum CompressionType where
maybeToEnum :: Int -> Maybe CompressionType
maybeToEnum 0 = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
NONE
maybeToEnum 1 = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
LZ4
maybeToEnum 2 = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
ZLIB
maybeToEnum 3 = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
ZSTD
maybeToEnum 4 = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
SNAPPY
maybeToEnum _ = Maybe CompressionType
forall a. Maybe a
Prelude.Nothing
showEnum :: CompressionType -> String
showEnum NONE = "NONE"
showEnum LZ4 = "LZ4"
showEnum ZLIB = "ZLIB"
showEnum ZSTD = "ZSTD"
showEnum SNAPPY = "SNAPPY"
readEnum :: String -> Maybe CompressionType
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "NONE" = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
NONE
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "LZ4" = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
LZ4
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ZLIB" = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
ZLIB
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ZSTD" = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
ZSTD
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SNAPPY" = CompressionType -> Maybe CompressionType
forall a. a -> Maybe a
Prelude.Just CompressionType
SNAPPY
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe CompressionType) -> Maybe CompressionType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe CompressionType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded CompressionType where
minBound :: CompressionType
minBound = CompressionType
NONE
maxBound :: CompressionType
maxBound = CompressionType
SNAPPY
instance Prelude.Enum CompressionType where
toEnum :: Int -> CompressionType
toEnum k__ :: Int
k__
= CompressionType
-> (CompressionType -> CompressionType)
-> Maybe CompressionType
-> CompressionType
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> CompressionType
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum CompressionType: "
(Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
CompressionType -> CompressionType
forall a. a -> a
Prelude.id
(Int -> Maybe CompressionType
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: CompressionType -> Int
fromEnum NONE = 0
fromEnum LZ4 = 1
fromEnum ZLIB = 2
fromEnum ZSTD = 3
fromEnum SNAPPY = 4
succ :: CompressionType -> CompressionType
succ SNAPPY
= String -> CompressionType
forall a. HasCallStack => String -> a
Prelude.error
"CompressionType.succ: bad argument SNAPPY. This value would be out of bounds."
succ NONE = CompressionType
LZ4
succ LZ4 = CompressionType
ZLIB
succ ZLIB = CompressionType
ZSTD
succ ZSTD = CompressionType
SNAPPY
pred :: CompressionType -> CompressionType
pred NONE
= String -> CompressionType
forall a. HasCallStack => String -> a
Prelude.error
"CompressionType.pred: bad argument NONE. This value would be out of bounds."
pred LZ4 = CompressionType
NONE
pred ZLIB = CompressionType
LZ4
pred ZSTD = CompressionType
ZLIB
pred SNAPPY = CompressionType
ZSTD
enumFrom :: CompressionType -> [CompressionType]
enumFrom = CompressionType -> [CompressionType]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: CompressionType -> CompressionType -> [CompressionType]
enumFromTo = CompressionType -> CompressionType -> [CompressionType]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: CompressionType -> CompressionType -> [CompressionType]
enumFromThen = CompressionType -> CompressionType -> [CompressionType]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: CompressionType
-> CompressionType -> CompressionType -> [CompressionType]
enumFromThenTo = CompressionType
-> CompressionType -> CompressionType -> [CompressionType]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault CompressionType where
fieldDefault :: CompressionType
fieldDefault = CompressionType
NONE
instance Control.DeepSeq.NFData CompressionType where
rnf :: CompressionType -> ()
rnf x__ :: CompressionType
x__ = CompressionType -> () -> ()
forall a b. a -> b -> b
Prelude.seq CompressionType
x__ ()
data EncryptionKeys
= EncryptionKeys'_constructor {EncryptionKeys -> Text
_EncryptionKeys'key :: !Data.Text.Text,
EncryptionKeys -> ByteString
_EncryptionKeys'value :: !Data.ByteString.ByteString,
EncryptionKeys -> Vector KeyValue
_EncryptionKeys'metadata :: !(Data.Vector.Vector KeyValue),
EncryptionKeys -> FieldSet
_EncryptionKeys'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (EncryptionKeys -> EncryptionKeys -> Bool
(EncryptionKeys -> EncryptionKeys -> Bool)
-> (EncryptionKeys -> EncryptionKeys -> Bool) -> Eq EncryptionKeys
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EncryptionKeys -> EncryptionKeys -> Bool
$c/= :: EncryptionKeys -> EncryptionKeys -> Bool
== :: EncryptionKeys -> EncryptionKeys -> Bool
$c== :: EncryptionKeys -> EncryptionKeys -> Bool
Prelude.Eq, Eq EncryptionKeys
Eq EncryptionKeys =>
(EncryptionKeys -> EncryptionKeys -> Ordering)
-> (EncryptionKeys -> EncryptionKeys -> Bool)
-> (EncryptionKeys -> EncryptionKeys -> Bool)
-> (EncryptionKeys -> EncryptionKeys -> Bool)
-> (EncryptionKeys -> EncryptionKeys -> Bool)
-> (EncryptionKeys -> EncryptionKeys -> EncryptionKeys)
-> (EncryptionKeys -> EncryptionKeys -> EncryptionKeys)
-> Ord EncryptionKeys
EncryptionKeys -> EncryptionKeys -> Bool
EncryptionKeys -> EncryptionKeys -> Ordering
EncryptionKeys -> EncryptionKeys -> EncryptionKeys
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EncryptionKeys -> EncryptionKeys -> EncryptionKeys
$cmin :: EncryptionKeys -> EncryptionKeys -> EncryptionKeys
max :: EncryptionKeys -> EncryptionKeys -> EncryptionKeys
$cmax :: EncryptionKeys -> EncryptionKeys -> EncryptionKeys
>= :: EncryptionKeys -> EncryptionKeys -> Bool
$c>= :: EncryptionKeys -> EncryptionKeys -> Bool
> :: EncryptionKeys -> EncryptionKeys -> Bool
$c> :: EncryptionKeys -> EncryptionKeys -> Bool
<= :: EncryptionKeys -> EncryptionKeys -> Bool
$c<= :: EncryptionKeys -> EncryptionKeys -> Bool
< :: EncryptionKeys -> EncryptionKeys -> Bool
$c< :: EncryptionKeys -> EncryptionKeys -> Bool
compare :: EncryptionKeys -> EncryptionKeys -> Ordering
$ccompare :: EncryptionKeys -> EncryptionKeys -> Ordering
$cp1Ord :: Eq EncryptionKeys
Prelude.Ord)
instance Prelude.Show EncryptionKeys where
showsPrec :: Int -> EncryptionKeys -> ShowS
showsPrec _ __x :: EncryptionKeys
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(EncryptionKeys -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort EncryptionKeys
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField EncryptionKeys "key" Data.Text.Text where
fieldOf :: Proxy# "key"
-> (Text -> f Text) -> EncryptionKeys -> f EncryptionKeys
fieldOf _
= ((Text -> f Text) -> EncryptionKeys -> f EncryptionKeys)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> EncryptionKeys
-> f EncryptionKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((EncryptionKeys -> Text)
-> (EncryptionKeys -> Text -> EncryptionKeys)
-> Lens EncryptionKeys EncryptionKeys Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
EncryptionKeys -> Text
_EncryptionKeys'key (\ x__ :: EncryptionKeys
x__ y__ :: Text
y__ -> EncryptionKeys
x__ {_EncryptionKeys'key :: Text
_EncryptionKeys'key = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField EncryptionKeys "value" Data.ByteString.ByteString where
fieldOf :: Proxy# "value"
-> (ByteString -> f ByteString)
-> EncryptionKeys
-> f EncryptionKeys
fieldOf _
= ((ByteString -> f ByteString)
-> EncryptionKeys -> f EncryptionKeys)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> EncryptionKeys
-> f EncryptionKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((EncryptionKeys -> ByteString)
-> (EncryptionKeys -> ByteString -> EncryptionKeys)
-> Lens EncryptionKeys EncryptionKeys ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
EncryptionKeys -> ByteString
_EncryptionKeys'value
(\ x__ :: EncryptionKeys
x__ y__ :: ByteString
y__ -> EncryptionKeys
x__ {_EncryptionKeys'value :: ByteString
_EncryptionKeys'value = ByteString
y__}))
(ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField EncryptionKeys "metadata" [KeyValue] where
fieldOf :: Proxy# "metadata"
-> ([KeyValue] -> f [KeyValue])
-> EncryptionKeys
-> f EncryptionKeys
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> EncryptionKeys -> f EncryptionKeys)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> EncryptionKeys
-> f EncryptionKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((EncryptionKeys -> Vector KeyValue)
-> (EncryptionKeys -> Vector KeyValue -> EncryptionKeys)
-> Lens
EncryptionKeys EncryptionKeys (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
EncryptionKeys -> Vector KeyValue
_EncryptionKeys'metadata
(\ x__ :: EncryptionKeys
x__ y__ :: Vector KeyValue
y__ -> EncryptionKeys
x__ {_EncryptionKeys'metadata :: Vector KeyValue
_EncryptionKeys'metadata = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField EncryptionKeys "vec'metadata" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'metadata"
-> (Vector KeyValue -> f (Vector KeyValue))
-> EncryptionKeys
-> f EncryptionKeys
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> EncryptionKeys -> f EncryptionKeys)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> EncryptionKeys
-> f EncryptionKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((EncryptionKeys -> Vector KeyValue)
-> (EncryptionKeys -> Vector KeyValue -> EncryptionKeys)
-> Lens
EncryptionKeys EncryptionKeys (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
EncryptionKeys -> Vector KeyValue
_EncryptionKeys'metadata
(\ x__ :: EncryptionKeys
x__ y__ :: Vector KeyValue
y__ -> EncryptionKeys
x__ {_EncryptionKeys'metadata :: Vector KeyValue
_EncryptionKeys'metadata = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message EncryptionKeys where
messageName :: Proxy EncryptionKeys -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.EncryptionKeys"
packedMessageDescriptor :: Proxy EncryptionKeys -> ByteString
packedMessageDescriptor _
= "\n\
\\SOEncryptionKeys\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\fR\ENQvalue\DC22\n\
\\bmetadata\CAN\ETX \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata"
packedFileDescriptor :: Proxy EncryptionKeys -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor EncryptionKeys)
fieldsByTag
= let
key__field_descriptor :: FieldDescriptor EncryptionKeys
key__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor EncryptionKeys Text
-> FieldDescriptor EncryptionKeys
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"key"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens EncryptionKeys EncryptionKeys Text Text
-> FieldAccessor EncryptionKeys Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key")) ::
Data.ProtoLens.FieldDescriptor EncryptionKeys
value__field_descriptor :: FieldDescriptor EncryptionKeys
value__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor EncryptionKeys ByteString
-> FieldDescriptor EncryptionKeys
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"value"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(WireDefault ByteString
-> Lens EncryptionKeys EncryptionKeys ByteString ByteString
-> FieldAccessor EncryptionKeys ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ByteString
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value")) ::
Data.ProtoLens.FieldDescriptor EncryptionKeys
metadata__field_descriptor :: FieldDescriptor EncryptionKeys
metadata__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor EncryptionKeys KeyValue
-> FieldDescriptor EncryptionKeys
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"metadata"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing
-> Lens' EncryptionKeys [KeyValue]
-> FieldAccessor EncryptionKeys KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"metadata")) ::
Data.ProtoLens.FieldDescriptor EncryptionKeys
in
[(Tag, FieldDescriptor EncryptionKeys)]
-> Map Tag (FieldDescriptor EncryptionKeys)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor EncryptionKeys
key__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor EncryptionKeys
value__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor EncryptionKeys
metadata__field_descriptor)]
unknownFields :: LensLike' f EncryptionKeys FieldSet
unknownFields
= (EncryptionKeys -> FieldSet)
-> (EncryptionKeys -> FieldSet -> EncryptionKeys)
-> Lens' EncryptionKeys FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
EncryptionKeys -> FieldSet
_EncryptionKeys'_unknownFields
(\ x__ :: EncryptionKeys
x__ y__ :: FieldSet
y__ -> EncryptionKeys
x__ {_EncryptionKeys'_unknownFields :: FieldSet
_EncryptionKeys'_unknownFields = FieldSet
y__})
defMessage :: EncryptionKeys
defMessage
= $WEncryptionKeys'_constructor :: Text -> ByteString -> Vector KeyValue -> FieldSet -> EncryptionKeys
EncryptionKeys'_constructor
{_EncryptionKeys'key :: Text
_EncryptionKeys'key = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_EncryptionKeys'value :: ByteString
_EncryptionKeys'value = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_EncryptionKeys'metadata :: Vector KeyValue
_EncryptionKeys'metadata = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_EncryptionKeys'_unknownFields :: FieldSet
_EncryptionKeys'_unknownFields = []}
parseMessage :: Parser EncryptionKeys
parseMessage
= let
loop ::
EncryptionKeys
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Bytes.Parser EncryptionKeys
loop :: EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop x :: EncryptionKeys
x required'key :: Bool
required'key required'value :: Bool
required'value mutable'metadata :: Growing Vector RealWorld KeyValue
mutable'metadata
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector KeyValue
frozen'metadata <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata)
(let
missing :: [String]
missing
= (if Bool
required'key then (:) "key" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'value then (:) "value" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
EncryptionKeys -> Parser EncryptionKeys
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter EncryptionKeys EncryptionKeys FieldSet FieldSet
-> (FieldSet -> FieldSet) -> EncryptionKeys -> EncryptionKeys
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter EncryptionKeys EncryptionKeys FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
EncryptionKeys EncryptionKeys (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> EncryptionKeys -> EncryptionKeys
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") Vector KeyValue
frozen'metadata EncryptionKeys
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"key"
EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop
(Setter EncryptionKeys EncryptionKeys Text Text
-> Text -> EncryptionKeys -> EncryptionKeys
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") Text
y EncryptionKeys
x)
Bool
Prelude.False
Bool
required'value
Growing Vector RealWorld KeyValue
mutable'metadata
18
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"value"
EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop
(Setter EncryptionKeys EncryptionKeys ByteString ByteString
-> ByteString -> EncryptionKeys -> EncryptionKeys
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") ByteString
y EncryptionKeys
x)
Bool
required'key
Bool
Prelude.False
Growing Vector RealWorld KeyValue
mutable'metadata
26
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"metadata"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'metadata KeyValue
y)
EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop EncryptionKeys
x Bool
required'key Bool
required'value Growing Vector RealWorld KeyValue
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop
(Setter EncryptionKeys EncryptionKeys FieldSet FieldSet
-> (FieldSet -> FieldSet) -> EncryptionKeys -> EncryptionKeys
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter EncryptionKeys EncryptionKeys FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) EncryptionKeys
x)
Bool
required'key
Bool
required'value
Growing Vector RealWorld KeyValue
mutable'metadata
in
Parser EncryptionKeys -> String -> Parser EncryptionKeys
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld KeyValue
mutable'metadata <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
EncryptionKeys
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser EncryptionKeys
loop
EncryptionKeys
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld KeyValue
mutable'metadata)
"EncryptionKeys"
buildMessage :: EncryptionKeys -> Builder
buildMessage
= \ _x :: EncryptionKeys
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text EncryptionKeys EncryptionKeys Text Text
-> EncryptionKeys -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") EncryptionKeys
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
(FoldLike
ByteString EncryptionKeys EncryptionKeys ByteString ByteString
-> EncryptionKeys -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") EncryptionKeys
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue)
EncryptionKeys
EncryptionKeys
(Vector KeyValue)
(Vector KeyValue)
-> EncryptionKeys -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'metadata" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'metadata") EncryptionKeys
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet EncryptionKeys EncryptionKeys FieldSet FieldSet
-> EncryptionKeys -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet EncryptionKeys EncryptionKeys FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields EncryptionKeys
_x))))
instance Control.DeepSeq.NFData EncryptionKeys where
rnf :: EncryptionKeys -> ()
rnf
= \ x__ :: EncryptionKeys
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(EncryptionKeys -> FieldSet
_EncryptionKeys'_unknownFields EncryptionKeys
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(EncryptionKeys -> Text
_EncryptionKeys'key EncryptionKeys
x__)
(ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(EncryptionKeys -> ByteString
_EncryptionKeys'value EncryptionKeys
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (EncryptionKeys -> Vector KeyValue
_EncryptionKeys'metadata EncryptionKeys
x__) ())))
data FeatureFlags
= FeatureFlags'_constructor {FeatureFlags -> Maybe Bool
_FeatureFlags'supportsAuthRefresh :: !(Prelude.Maybe Prelude.Bool),
FeatureFlags -> FieldSet
_FeatureFlags'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (FeatureFlags -> FeatureFlags -> Bool
(FeatureFlags -> FeatureFlags -> Bool)
-> (FeatureFlags -> FeatureFlags -> Bool) -> Eq FeatureFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeatureFlags -> FeatureFlags -> Bool
$c/= :: FeatureFlags -> FeatureFlags -> Bool
== :: FeatureFlags -> FeatureFlags -> Bool
$c== :: FeatureFlags -> FeatureFlags -> Bool
Prelude.Eq, Eq FeatureFlags
Eq FeatureFlags =>
(FeatureFlags -> FeatureFlags -> Ordering)
-> (FeatureFlags -> FeatureFlags -> Bool)
-> (FeatureFlags -> FeatureFlags -> Bool)
-> (FeatureFlags -> FeatureFlags -> Bool)
-> (FeatureFlags -> FeatureFlags -> Bool)
-> (FeatureFlags -> FeatureFlags -> FeatureFlags)
-> (FeatureFlags -> FeatureFlags -> FeatureFlags)
-> Ord FeatureFlags
FeatureFlags -> FeatureFlags -> Bool
FeatureFlags -> FeatureFlags -> Ordering
FeatureFlags -> FeatureFlags -> FeatureFlags
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FeatureFlags -> FeatureFlags -> FeatureFlags
$cmin :: FeatureFlags -> FeatureFlags -> FeatureFlags
max :: FeatureFlags -> FeatureFlags -> FeatureFlags
$cmax :: FeatureFlags -> FeatureFlags -> FeatureFlags
>= :: FeatureFlags -> FeatureFlags -> Bool
$c>= :: FeatureFlags -> FeatureFlags -> Bool
> :: FeatureFlags -> FeatureFlags -> Bool
$c> :: FeatureFlags -> FeatureFlags -> Bool
<= :: FeatureFlags -> FeatureFlags -> Bool
$c<= :: FeatureFlags -> FeatureFlags -> Bool
< :: FeatureFlags -> FeatureFlags -> Bool
$c< :: FeatureFlags -> FeatureFlags -> Bool
compare :: FeatureFlags -> FeatureFlags -> Ordering
$ccompare :: FeatureFlags -> FeatureFlags -> Ordering
$cp1Ord :: Eq FeatureFlags
Prelude.Ord)
instance Prelude.Show FeatureFlags where
showsPrec :: Int -> FeatureFlags -> ShowS
showsPrec _ __x :: FeatureFlags
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(FeatureFlags -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort FeatureFlags
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField FeatureFlags "supportsAuthRefresh" Prelude.Bool where
fieldOf :: Proxy# "supportsAuthRefresh"
-> (Bool -> f Bool) -> FeatureFlags -> f FeatureFlags
fieldOf _
= ((Maybe Bool -> f (Maybe Bool)) -> FeatureFlags -> f FeatureFlags)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> FeatureFlags
-> f FeatureFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FeatureFlags -> Maybe Bool)
-> (FeatureFlags -> Maybe Bool -> FeatureFlags)
-> Lens FeatureFlags FeatureFlags (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FeatureFlags -> Maybe Bool
_FeatureFlags'supportsAuthRefresh
(\ x__ :: FeatureFlags
x__ y__ :: Maybe Bool
y__ -> FeatureFlags
x__ {_FeatureFlags'supportsAuthRefresh :: Maybe Bool
_FeatureFlags'supportsAuthRefresh = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField FeatureFlags "maybe'supportsAuthRefresh" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'supportsAuthRefresh"
-> (Maybe Bool -> f (Maybe Bool)) -> FeatureFlags -> f FeatureFlags
fieldOf _
= ((Maybe Bool -> f (Maybe Bool)) -> FeatureFlags -> f FeatureFlags)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> FeatureFlags
-> f FeatureFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FeatureFlags -> Maybe Bool)
-> (FeatureFlags -> Maybe Bool -> FeatureFlags)
-> Lens FeatureFlags FeatureFlags (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FeatureFlags -> Maybe Bool
_FeatureFlags'supportsAuthRefresh
(\ x__ :: FeatureFlags
x__ y__ :: Maybe Bool
y__ -> FeatureFlags
x__ {_FeatureFlags'supportsAuthRefresh :: Maybe Bool
_FeatureFlags'supportsAuthRefresh = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message FeatureFlags where
messageName :: Proxy FeatureFlags -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.FeatureFlags"
packedMessageDescriptor :: Proxy FeatureFlags -> ByteString
packedMessageDescriptor _
= "\n\
\\fFeatureFlags\DC29\n\
\\NAKsupports_auth_refresh\CAN\SOH \SOH(\b:\ENQfalseR\DC3supportsAuthRefresh"
packedFileDescriptor :: Proxy FeatureFlags -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor FeatureFlags)
fieldsByTag
= let
supportsAuthRefresh__field_descriptor :: FieldDescriptor FeatureFlags
supportsAuthRefresh__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor FeatureFlags Bool
-> FieldDescriptor FeatureFlags
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"supports_auth_refresh"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens FeatureFlags FeatureFlags (Maybe Bool) (Maybe Bool)
-> FieldAccessor FeatureFlags Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'supportsAuthRefresh" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'supportsAuthRefresh")) ::
Data.ProtoLens.FieldDescriptor FeatureFlags
in
[(Tag, FieldDescriptor FeatureFlags)]
-> Map Tag (FieldDescriptor FeatureFlags)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor FeatureFlags
supportsAuthRefresh__field_descriptor)]
unknownFields :: LensLike' f FeatureFlags FieldSet
unknownFields
= (FeatureFlags -> FieldSet)
-> (FeatureFlags -> FieldSet -> FeatureFlags)
-> Lens' FeatureFlags FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FeatureFlags -> FieldSet
_FeatureFlags'_unknownFields
(\ x__ :: FeatureFlags
x__ y__ :: FieldSet
y__ -> FeatureFlags
x__ {_FeatureFlags'_unknownFields :: FieldSet
_FeatureFlags'_unknownFields = FieldSet
y__})
defMessage :: FeatureFlags
defMessage
= $WFeatureFlags'_constructor :: Maybe Bool -> FieldSet -> FeatureFlags
FeatureFlags'_constructor
{_FeatureFlags'supportsAuthRefresh :: Maybe Bool
_FeatureFlags'supportsAuthRefresh = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_FeatureFlags'_unknownFields :: FieldSet
_FeatureFlags'_unknownFields = []}
parseMessage :: Parser FeatureFlags
parseMessage
= let
loop ::
FeatureFlags -> Data.ProtoLens.Encoding.Bytes.Parser FeatureFlags
loop :: FeatureFlags -> Parser FeatureFlags
loop x :: FeatureFlags
x
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let missing :: [a]
missing = []
in
if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
FeatureFlags -> Parser FeatureFlags
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter FeatureFlags FeatureFlags FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FeatureFlags -> FeatureFlags
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter FeatureFlags FeatureFlags FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) FeatureFlags
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"supports_auth_refresh"
FeatureFlags -> Parser FeatureFlags
loop
(Setter FeatureFlags FeatureFlags Bool Bool
-> Bool -> FeatureFlags -> FeatureFlags
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "supportsAuthRefresh" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"supportsAuthRefresh") Bool
y FeatureFlags
x)
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
FeatureFlags -> Parser FeatureFlags
loop
(Setter FeatureFlags FeatureFlags FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FeatureFlags -> FeatureFlags
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter FeatureFlags FeatureFlags FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) FeatureFlags
x)
in
Parser FeatureFlags -> String -> Parser FeatureFlags
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do FeatureFlags -> Parser FeatureFlags
loop FeatureFlags
forall msg. Message msg => msg
Data.ProtoLens.defMessage) "FeatureFlags"
buildMessage :: FeatureFlags -> Builder
buildMessage
= \ _x :: FeatureFlags
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool) FeatureFlags FeatureFlags (Maybe Bool) (Maybe Bool)
-> FeatureFlags -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'supportsAuthRefresh" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'supportsAuthRefresh") FeatureFlags
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet FeatureFlags FeatureFlags FieldSet FieldSet
-> FeatureFlags -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet FeatureFlags FeatureFlags FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields FeatureFlags
_x))
instance Control.DeepSeq.NFData FeatureFlags where
rnf :: FeatureFlags -> ()
rnf
= \ x__ :: FeatureFlags
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FeatureFlags -> FieldSet
_FeatureFlags'_unknownFields FeatureFlags
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FeatureFlags -> Maybe Bool
_FeatureFlags'supportsAuthRefresh FeatureFlags
x__) ())
data IntRange
= IntRange'_constructor {IntRange -> Int32
_IntRange'start :: !Data.Int.Int32,
IntRange -> Int32
_IntRange'end :: !Data.Int.Int32,
IntRange -> FieldSet
_IntRange'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (IntRange -> IntRange -> Bool
(IntRange -> IntRange -> Bool)
-> (IntRange -> IntRange -> Bool) -> Eq IntRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntRange -> IntRange -> Bool
$c/= :: IntRange -> IntRange -> Bool
== :: IntRange -> IntRange -> Bool
$c== :: IntRange -> IntRange -> Bool
Prelude.Eq, Eq IntRange
Eq IntRange =>
(IntRange -> IntRange -> Ordering)
-> (IntRange -> IntRange -> Bool)
-> (IntRange -> IntRange -> Bool)
-> (IntRange -> IntRange -> Bool)
-> (IntRange -> IntRange -> Bool)
-> (IntRange -> IntRange -> IntRange)
-> (IntRange -> IntRange -> IntRange)
-> Ord IntRange
IntRange -> IntRange -> Bool
IntRange -> IntRange -> Ordering
IntRange -> IntRange -> IntRange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IntRange -> IntRange -> IntRange
$cmin :: IntRange -> IntRange -> IntRange
max :: IntRange -> IntRange -> IntRange
$cmax :: IntRange -> IntRange -> IntRange
>= :: IntRange -> IntRange -> Bool
$c>= :: IntRange -> IntRange -> Bool
> :: IntRange -> IntRange -> Bool
$c> :: IntRange -> IntRange -> Bool
<= :: IntRange -> IntRange -> Bool
$c<= :: IntRange -> IntRange -> Bool
< :: IntRange -> IntRange -> Bool
$c< :: IntRange -> IntRange -> Bool
compare :: IntRange -> IntRange -> Ordering
$ccompare :: IntRange -> IntRange -> Ordering
$cp1Ord :: Eq IntRange
Prelude.Ord)
instance Prelude.Show IntRange where
showsPrec :: Int -> IntRange -> ShowS
showsPrec _ __x :: IntRange
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(IntRange -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort IntRange
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField IntRange "start" Data.Int.Int32 where
fieldOf :: Proxy# "start" -> (Int32 -> f Int32) -> IntRange -> f IntRange
fieldOf _
= ((Int32 -> f Int32) -> IntRange -> f IntRange)
-> ((Int32 -> f Int32) -> Int32 -> f Int32)
-> (Int32 -> f Int32)
-> IntRange
-> f IntRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((IntRange -> Int32)
-> (IntRange -> Int32 -> IntRange)
-> Lens IntRange IntRange Int32 Int32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
IntRange -> Int32
_IntRange'start (\ x__ :: IntRange
x__ y__ :: Int32
y__ -> IntRange
x__ {_IntRange'start :: Int32
_IntRange'start = Int32
y__}))
(Int32 -> f Int32) -> Int32 -> f Int32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField IntRange "end" Data.Int.Int32 where
fieldOf :: Proxy# "end" -> (Int32 -> f Int32) -> IntRange -> f IntRange
fieldOf _
= ((Int32 -> f Int32) -> IntRange -> f IntRange)
-> ((Int32 -> f Int32) -> Int32 -> f Int32)
-> (Int32 -> f Int32)
-> IntRange
-> f IntRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((IntRange -> Int32)
-> (IntRange -> Int32 -> IntRange)
-> Lens IntRange IntRange Int32 Int32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
IntRange -> Int32
_IntRange'end (\ x__ :: IntRange
x__ y__ :: Int32
y__ -> IntRange
x__ {_IntRange'end :: Int32
_IntRange'end = Int32
y__}))
(Int32 -> f Int32) -> Int32 -> f Int32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message IntRange where
messageName :: Proxy IntRange -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.IntRange"
packedMessageDescriptor :: Proxy IntRange -> ByteString
packedMessageDescriptor _
= "\n\
\\bIntRange\DC2\DC4\n\
\\ENQstart\CAN\SOH \STX(\ENQR\ENQstart\DC2\DLE\n\
\\ETXend\CAN\STX \STX(\ENQR\ETXend"
packedFileDescriptor :: Proxy IntRange -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor IntRange)
fieldsByTag
= let
start__field_descriptor :: FieldDescriptor IntRange
start__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor IntRange Int32
-> FieldDescriptor IntRange
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"start"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(WireDefault Int32
-> Lens IntRange IntRange Int32 Int32
-> FieldAccessor IntRange Int32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Int32
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "start" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"start")) ::
Data.ProtoLens.FieldDescriptor IntRange
end__field_descriptor :: FieldDescriptor IntRange
end__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor IntRange Int32
-> FieldDescriptor IntRange
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"end"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(WireDefault Int32
-> Lens IntRange IntRange Int32 Int32
-> FieldAccessor IntRange Int32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Int32
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "end" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"end")) ::
Data.ProtoLens.FieldDescriptor IntRange
in
[(Tag, FieldDescriptor IntRange)]
-> Map Tag (FieldDescriptor IntRange)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor IntRange
start__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor IntRange
end__field_descriptor)]
unknownFields :: LensLike' f IntRange FieldSet
unknownFields
= (IntRange -> FieldSet)
-> (IntRange -> FieldSet -> IntRange) -> Lens' IntRange FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
IntRange -> FieldSet
_IntRange'_unknownFields
(\ x__ :: IntRange
x__ y__ :: FieldSet
y__ -> IntRange
x__ {_IntRange'_unknownFields :: FieldSet
_IntRange'_unknownFields = FieldSet
y__})
defMessage :: IntRange
defMessage
= $WIntRange'_constructor :: Int32 -> Int32 -> FieldSet -> IntRange
IntRange'_constructor
{_IntRange'start :: Int32
_IntRange'start = Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_IntRange'end :: Int32
_IntRange'end = Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_IntRange'_unknownFields :: FieldSet
_IntRange'_unknownFields = []}
parseMessage :: Parser IntRange
parseMessage
= let
loop ::
IntRange
-> Prelude.Bool
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser IntRange
loop :: IntRange -> Bool -> Bool -> Parser IntRange
loop x :: IntRange
x required'end :: Bool
required'end required'start :: Bool
required'start
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'end then (:) "end" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'start then (:) "start" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
IntRange -> Parser IntRange
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter IntRange IntRange FieldSet FieldSet
-> (FieldSet -> FieldSet) -> IntRange -> IntRange
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter IntRange IntRange FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) IntRange
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"start"
IntRange -> Bool -> Bool -> Parser IntRange
loop
(Setter IntRange IntRange Int32 Int32
-> Int32 -> IntRange -> IntRange
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "start" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"start") Int32
y IntRange
x)
Bool
required'end
Bool
Prelude.False
16
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"end"
IntRange -> Bool -> Bool -> Parser IntRange
loop
(Setter IntRange IntRange Int32 Int32
-> Int32 -> IntRange -> IntRange
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "end" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"end") Int32
y IntRange
x)
Bool
Prelude.False
Bool
required'start
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
IntRange -> Bool -> Bool -> Parser IntRange
loop
(Setter IntRange IntRange FieldSet FieldSet
-> (FieldSet -> FieldSet) -> IntRange -> IntRange
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter IntRange IntRange FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) IntRange
x)
Bool
required'end
Bool
required'start
in
Parser IntRange -> String -> Parser IntRange
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do IntRange -> Bool -> Bool -> Parser IntRange
loop IntRange
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"IntRange"
buildMessage :: IntRange -> Builder
buildMessage
= \ _x :: IntRange
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(FoldLike Int32 IntRange IntRange Int32 Int32 -> IntRange -> Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "start" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"start") IntRange
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(FoldLike Int32 IntRange IntRange Int32 Int32 -> IntRange -> Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "end" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"end") IntRange
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet IntRange IntRange FieldSet FieldSet
-> IntRange -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet IntRange IntRange FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields IntRange
_x)))
instance Control.DeepSeq.NFData IntRange where
rnf :: IntRange -> ()
rnf
= \ x__ :: IntRange
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(IntRange -> FieldSet
_IntRange'_unknownFields IntRange
x__)
(Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(IntRange -> Int32
_IntRange'start IntRange
x__)
(Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (IntRange -> Int32
_IntRange'end IntRange
x__) ()))
data KeyLongValue
= KeyLongValue'_constructor {KeyLongValue -> Text
_KeyLongValue'key :: !Data.Text.Text,
KeyLongValue -> Word64
_KeyLongValue'value :: !Data.Word.Word64,
KeyLongValue -> FieldSet
_KeyLongValue'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (KeyLongValue -> KeyLongValue -> Bool
(KeyLongValue -> KeyLongValue -> Bool)
-> (KeyLongValue -> KeyLongValue -> Bool) -> Eq KeyLongValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyLongValue -> KeyLongValue -> Bool
$c/= :: KeyLongValue -> KeyLongValue -> Bool
== :: KeyLongValue -> KeyLongValue -> Bool
$c== :: KeyLongValue -> KeyLongValue -> Bool
Prelude.Eq, Eq KeyLongValue
Eq KeyLongValue =>
(KeyLongValue -> KeyLongValue -> Ordering)
-> (KeyLongValue -> KeyLongValue -> Bool)
-> (KeyLongValue -> KeyLongValue -> Bool)
-> (KeyLongValue -> KeyLongValue -> Bool)
-> (KeyLongValue -> KeyLongValue -> Bool)
-> (KeyLongValue -> KeyLongValue -> KeyLongValue)
-> (KeyLongValue -> KeyLongValue -> KeyLongValue)
-> Ord KeyLongValue
KeyLongValue -> KeyLongValue -> Bool
KeyLongValue -> KeyLongValue -> Ordering
KeyLongValue -> KeyLongValue -> KeyLongValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeyLongValue -> KeyLongValue -> KeyLongValue
$cmin :: KeyLongValue -> KeyLongValue -> KeyLongValue
max :: KeyLongValue -> KeyLongValue -> KeyLongValue
$cmax :: KeyLongValue -> KeyLongValue -> KeyLongValue
>= :: KeyLongValue -> KeyLongValue -> Bool
$c>= :: KeyLongValue -> KeyLongValue -> Bool
> :: KeyLongValue -> KeyLongValue -> Bool
$c> :: KeyLongValue -> KeyLongValue -> Bool
<= :: KeyLongValue -> KeyLongValue -> Bool
$c<= :: KeyLongValue -> KeyLongValue -> Bool
< :: KeyLongValue -> KeyLongValue -> Bool
$c< :: KeyLongValue -> KeyLongValue -> Bool
compare :: KeyLongValue -> KeyLongValue -> Ordering
$ccompare :: KeyLongValue -> KeyLongValue -> Ordering
$cp1Ord :: Eq KeyLongValue
Prelude.Ord)
instance Prelude.Show KeyLongValue where
showsPrec :: Int -> KeyLongValue -> ShowS
showsPrec _ __x :: KeyLongValue
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(KeyLongValue -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort KeyLongValue
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField KeyLongValue "key" Data.Text.Text where
fieldOf :: Proxy# "key" -> (Text -> f Text) -> KeyLongValue -> f KeyLongValue
fieldOf _
= ((Text -> f Text) -> KeyLongValue -> f KeyLongValue)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> KeyLongValue
-> f KeyLongValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeyLongValue -> Text)
-> (KeyLongValue -> Text -> KeyLongValue)
-> Lens KeyLongValue KeyLongValue Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyLongValue -> Text
_KeyLongValue'key (\ x__ :: KeyLongValue
x__ y__ :: Text
y__ -> KeyLongValue
x__ {_KeyLongValue'key :: Text
_KeyLongValue'key = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField KeyLongValue "value" Data.Word.Word64 where
fieldOf :: Proxy# "value"
-> (Word64 -> f Word64) -> KeyLongValue -> f KeyLongValue
fieldOf _
= ((Word64 -> f Word64) -> KeyLongValue -> f KeyLongValue)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> KeyLongValue
-> f KeyLongValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeyLongValue -> Word64)
-> (KeyLongValue -> Word64 -> KeyLongValue)
-> Lens KeyLongValue KeyLongValue Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyLongValue -> Word64
_KeyLongValue'value (\ x__ :: KeyLongValue
x__ y__ :: Word64
y__ -> KeyLongValue
x__ {_KeyLongValue'value :: Word64
_KeyLongValue'value = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message KeyLongValue where
messageName :: Proxy KeyLongValue -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.KeyLongValue"
packedMessageDescriptor :: Proxy KeyLongValue -> ByteString
packedMessageDescriptor _
= "\n\
\\fKeyLongValue\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\EOTR\ENQvalue"
packedFileDescriptor :: Proxy KeyLongValue -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor KeyLongValue)
fieldsByTag
= let
key__field_descriptor :: FieldDescriptor KeyLongValue
key__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor KeyLongValue Text
-> FieldDescriptor KeyLongValue
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"key"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens KeyLongValue KeyLongValue Text Text
-> FieldAccessor KeyLongValue Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key")) ::
Data.ProtoLens.FieldDescriptor KeyLongValue
value__field_descriptor :: FieldDescriptor KeyLongValue
value__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor KeyLongValue Word64
-> FieldDescriptor KeyLongValue
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"value"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens KeyLongValue KeyLongValue Word64 Word64
-> FieldAccessor KeyLongValue Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value")) ::
Data.ProtoLens.FieldDescriptor KeyLongValue
in
[(Tag, FieldDescriptor KeyLongValue)]
-> Map Tag (FieldDescriptor KeyLongValue)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor KeyLongValue
key__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor KeyLongValue
value__field_descriptor)]
unknownFields :: LensLike' f KeyLongValue FieldSet
unknownFields
= (KeyLongValue -> FieldSet)
-> (KeyLongValue -> FieldSet -> KeyLongValue)
-> Lens' KeyLongValue FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyLongValue -> FieldSet
_KeyLongValue'_unknownFields
(\ x__ :: KeyLongValue
x__ y__ :: FieldSet
y__ -> KeyLongValue
x__ {_KeyLongValue'_unknownFields :: FieldSet
_KeyLongValue'_unknownFields = FieldSet
y__})
defMessage :: KeyLongValue
defMessage
= $WKeyLongValue'_constructor :: Text -> Word64 -> FieldSet -> KeyLongValue
KeyLongValue'_constructor
{_KeyLongValue'key :: Text
_KeyLongValue'key = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_KeyLongValue'value :: Word64
_KeyLongValue'value = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_KeyLongValue'_unknownFields :: FieldSet
_KeyLongValue'_unknownFields = []}
parseMessage :: Parser KeyLongValue
parseMessage
= let
loop ::
KeyLongValue
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser KeyLongValue
loop :: KeyLongValue -> Bool -> Bool -> Parser KeyLongValue
loop x :: KeyLongValue
x required'key :: Bool
required'key required'value :: Bool
required'value
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'key then (:) "key" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'value then (:) "value" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
KeyLongValue -> Parser KeyLongValue
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter KeyLongValue KeyLongValue FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeyLongValue -> KeyLongValue
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeyLongValue KeyLongValue FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) KeyLongValue
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"key"
KeyLongValue -> Bool -> Bool -> Parser KeyLongValue
loop
(Setter KeyLongValue KeyLongValue Text Text
-> Text -> KeyLongValue -> KeyLongValue
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") Text
y KeyLongValue
x)
Bool
Prelude.False
Bool
required'value
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "value"
KeyLongValue -> Bool -> Bool -> Parser KeyLongValue
loop
(Setter KeyLongValue KeyLongValue Word64 Word64
-> Word64 -> KeyLongValue -> KeyLongValue
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") Word64
y KeyLongValue
x)
Bool
required'key
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
KeyLongValue -> Bool -> Bool -> Parser KeyLongValue
loop
(Setter KeyLongValue KeyLongValue FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeyLongValue -> KeyLongValue
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeyLongValue KeyLongValue FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) KeyLongValue
x)
Bool
required'key
Bool
required'value
in
Parser KeyLongValue -> String -> Parser KeyLongValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do KeyLongValue -> Bool -> Bool -> Parser KeyLongValue
loop KeyLongValue
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"KeyLongValue"
buildMessage :: KeyLongValue -> Builder
buildMessage
= \ _x :: KeyLongValue
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text KeyLongValue KeyLongValue Text Text
-> KeyLongValue -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") KeyLongValue
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 KeyLongValue KeyLongValue Word64 Word64
-> KeyLongValue -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") KeyLongValue
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet KeyLongValue KeyLongValue FieldSet FieldSet
-> KeyLongValue -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet KeyLongValue KeyLongValue FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields KeyLongValue
_x)))
instance Control.DeepSeq.NFData KeyLongValue where
rnf :: KeyLongValue -> ()
rnf
= \ x__ :: KeyLongValue
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeyLongValue -> FieldSet
_KeyLongValue'_unknownFields KeyLongValue
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeyLongValue -> Text
_KeyLongValue'key KeyLongValue
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (KeyLongValue -> Word64
_KeyLongValue'value KeyLongValue
x__) ()))
data KeySharedMeta
= KeySharedMeta'_constructor {KeySharedMeta -> KeySharedMode
_KeySharedMeta'keySharedMode :: !KeySharedMode,
KeySharedMeta -> Vector IntRange
_KeySharedMeta'hashRanges :: !(Data.Vector.Vector IntRange),
KeySharedMeta -> Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery :: !(Prelude.Maybe Prelude.Bool),
KeySharedMeta -> FieldSet
_KeySharedMeta'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (KeySharedMeta -> KeySharedMeta -> Bool
(KeySharedMeta -> KeySharedMeta -> Bool)
-> (KeySharedMeta -> KeySharedMeta -> Bool) -> Eq KeySharedMeta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeySharedMeta -> KeySharedMeta -> Bool
$c/= :: KeySharedMeta -> KeySharedMeta -> Bool
== :: KeySharedMeta -> KeySharedMeta -> Bool
$c== :: KeySharedMeta -> KeySharedMeta -> Bool
Prelude.Eq, Eq KeySharedMeta
Eq KeySharedMeta =>
(KeySharedMeta -> KeySharedMeta -> Ordering)
-> (KeySharedMeta -> KeySharedMeta -> Bool)
-> (KeySharedMeta -> KeySharedMeta -> Bool)
-> (KeySharedMeta -> KeySharedMeta -> Bool)
-> (KeySharedMeta -> KeySharedMeta -> Bool)
-> (KeySharedMeta -> KeySharedMeta -> KeySharedMeta)
-> (KeySharedMeta -> KeySharedMeta -> KeySharedMeta)
-> Ord KeySharedMeta
KeySharedMeta -> KeySharedMeta -> Bool
KeySharedMeta -> KeySharedMeta -> Ordering
KeySharedMeta -> KeySharedMeta -> KeySharedMeta
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeySharedMeta -> KeySharedMeta -> KeySharedMeta
$cmin :: KeySharedMeta -> KeySharedMeta -> KeySharedMeta
max :: KeySharedMeta -> KeySharedMeta -> KeySharedMeta
$cmax :: KeySharedMeta -> KeySharedMeta -> KeySharedMeta
>= :: KeySharedMeta -> KeySharedMeta -> Bool
$c>= :: KeySharedMeta -> KeySharedMeta -> Bool
> :: KeySharedMeta -> KeySharedMeta -> Bool
$c> :: KeySharedMeta -> KeySharedMeta -> Bool
<= :: KeySharedMeta -> KeySharedMeta -> Bool
$c<= :: KeySharedMeta -> KeySharedMeta -> Bool
< :: KeySharedMeta -> KeySharedMeta -> Bool
$c< :: KeySharedMeta -> KeySharedMeta -> Bool
compare :: KeySharedMeta -> KeySharedMeta -> Ordering
$ccompare :: KeySharedMeta -> KeySharedMeta -> Ordering
$cp1Ord :: Eq KeySharedMeta
Prelude.Ord)
instance Prelude.Show KeySharedMeta where
showsPrec :: Int -> KeySharedMeta -> ShowS
showsPrec _ __x :: KeySharedMeta
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(KeySharedMeta -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort KeySharedMeta
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField KeySharedMeta "keySharedMode" KeySharedMode where
fieldOf :: Proxy# "keySharedMode"
-> (KeySharedMode -> f KeySharedMode)
-> KeySharedMeta
-> f KeySharedMeta
fieldOf _
= ((KeySharedMode -> f KeySharedMode)
-> KeySharedMeta -> f KeySharedMeta)
-> ((KeySharedMode -> f KeySharedMode)
-> KeySharedMode -> f KeySharedMode)
-> (KeySharedMode -> f KeySharedMode)
-> KeySharedMeta
-> f KeySharedMeta
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeySharedMeta -> KeySharedMode)
-> (KeySharedMeta -> KeySharedMode -> KeySharedMeta)
-> Lens KeySharedMeta KeySharedMeta KeySharedMode KeySharedMode
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> KeySharedMode
_KeySharedMeta'keySharedMode
(\ x__ :: KeySharedMeta
x__ y__ :: KeySharedMode
y__ -> KeySharedMeta
x__ {_KeySharedMeta'keySharedMode :: KeySharedMode
_KeySharedMeta'keySharedMode = KeySharedMode
y__}))
(KeySharedMode -> f KeySharedMode)
-> KeySharedMode -> f KeySharedMode
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField KeySharedMeta "hashRanges" [IntRange] where
fieldOf :: Proxy# "hashRanges"
-> ([IntRange] -> f [IntRange]) -> KeySharedMeta -> f KeySharedMeta
fieldOf _
= ((Vector IntRange -> f (Vector IntRange))
-> KeySharedMeta -> f KeySharedMeta)
-> (([IntRange] -> f [IntRange])
-> Vector IntRange -> f (Vector IntRange))
-> ([IntRange] -> f [IntRange])
-> KeySharedMeta
-> f KeySharedMeta
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeySharedMeta -> Vector IntRange)
-> (KeySharedMeta -> Vector IntRange -> KeySharedMeta)
-> Lens
KeySharedMeta KeySharedMeta (Vector IntRange) (Vector IntRange)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> Vector IntRange
_KeySharedMeta'hashRanges
(\ x__ :: KeySharedMeta
x__ y__ :: Vector IntRange
y__ -> KeySharedMeta
x__ {_KeySharedMeta'hashRanges :: Vector IntRange
_KeySharedMeta'hashRanges = Vector IntRange
y__}))
((Vector IntRange -> [IntRange])
-> (Vector IntRange -> [IntRange] -> Vector IntRange)
-> Lens (Vector IntRange) (Vector IntRange) [IntRange] [IntRange]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector IntRange -> [IntRange]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [IntRange]
y__ -> [IntRange] -> Vector IntRange
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [IntRange]
y__))
instance Data.ProtoLens.Field.HasField KeySharedMeta "vec'hashRanges" (Data.Vector.Vector IntRange) where
fieldOf :: Proxy# "vec'hashRanges"
-> (Vector IntRange -> f (Vector IntRange))
-> KeySharedMeta
-> f KeySharedMeta
fieldOf _
= ((Vector IntRange -> f (Vector IntRange))
-> KeySharedMeta -> f KeySharedMeta)
-> ((Vector IntRange -> f (Vector IntRange))
-> Vector IntRange -> f (Vector IntRange))
-> (Vector IntRange -> f (Vector IntRange))
-> KeySharedMeta
-> f KeySharedMeta
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeySharedMeta -> Vector IntRange)
-> (KeySharedMeta -> Vector IntRange -> KeySharedMeta)
-> Lens
KeySharedMeta KeySharedMeta (Vector IntRange) (Vector IntRange)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> Vector IntRange
_KeySharedMeta'hashRanges
(\ x__ :: KeySharedMeta
x__ y__ :: Vector IntRange
y__ -> KeySharedMeta
x__ {_KeySharedMeta'hashRanges :: Vector IntRange
_KeySharedMeta'hashRanges = Vector IntRange
y__}))
(Vector IntRange -> f (Vector IntRange))
-> Vector IntRange -> f (Vector IntRange)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField KeySharedMeta "allowOutOfOrderDelivery" Prelude.Bool where
fieldOf :: Proxy# "allowOutOfOrderDelivery"
-> (Bool -> f Bool) -> KeySharedMeta -> f KeySharedMeta
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> KeySharedMeta -> f KeySharedMeta)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> KeySharedMeta
-> f KeySharedMeta
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeySharedMeta -> Maybe Bool)
-> (KeySharedMeta -> Maybe Bool -> KeySharedMeta)
-> Lens KeySharedMeta KeySharedMeta (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery
(\ x__ :: KeySharedMeta
x__ y__ :: Maybe Bool
y__ -> KeySharedMeta
x__ {_KeySharedMeta'allowOutOfOrderDelivery :: Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField KeySharedMeta "maybe'allowOutOfOrderDelivery" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'allowOutOfOrderDelivery"
-> (Maybe Bool -> f (Maybe Bool))
-> KeySharedMeta
-> f KeySharedMeta
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> KeySharedMeta -> f KeySharedMeta)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> KeySharedMeta
-> f KeySharedMeta
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeySharedMeta -> Maybe Bool)
-> (KeySharedMeta -> Maybe Bool -> KeySharedMeta)
-> Lens KeySharedMeta KeySharedMeta (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery
(\ x__ :: KeySharedMeta
x__ y__ :: Maybe Bool
y__ -> KeySharedMeta
x__ {_KeySharedMeta'allowOutOfOrderDelivery :: Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message KeySharedMeta where
messageName :: Proxy KeySharedMeta -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.KeySharedMeta"
packedMessageDescriptor :: Proxy KeySharedMeta -> ByteString
packedMessageDescriptor _
= "\n\
\\rKeySharedMeta\DC2A\n\
\\rkeySharedMode\CAN\SOH \STX(\SO2\ESC.pulsar.proto.KeySharedModeR\rkeySharedMode\DC26\n\
\\n\
\hashRanges\CAN\ETX \ETX(\v2\SYN.pulsar.proto.IntRangeR\n\
\hashRanges\DC2?\n\
\\ETBallowOutOfOrderDelivery\CAN\EOT \SOH(\b:\ENQfalseR\ETBallowOutOfOrderDelivery"
packedFileDescriptor :: Proxy KeySharedMeta -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor KeySharedMeta)
fieldsByTag
= let
keySharedMode__field_descriptor :: FieldDescriptor KeySharedMeta
keySharedMode__field_descriptor
= String
-> FieldTypeDescriptor KeySharedMode
-> FieldAccessor KeySharedMeta KeySharedMode
-> FieldDescriptor KeySharedMeta
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"keySharedMode"
(ScalarField KeySharedMode -> FieldTypeDescriptor KeySharedMode
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField KeySharedMode
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor KeySharedMode)
(WireDefault KeySharedMode
-> Lens KeySharedMeta KeySharedMeta KeySharedMode KeySharedMode
-> FieldAccessor KeySharedMeta KeySharedMode
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault KeySharedMode
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "keySharedMode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"keySharedMode")) ::
Data.ProtoLens.FieldDescriptor KeySharedMeta
hashRanges__field_descriptor :: FieldDescriptor KeySharedMeta
hashRanges__field_descriptor
= String
-> FieldTypeDescriptor IntRange
-> FieldAccessor KeySharedMeta IntRange
-> FieldDescriptor KeySharedMeta
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"hashRanges"
(MessageOrGroup -> FieldTypeDescriptor IntRange
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor IntRange)
(Packing
-> Lens' KeySharedMeta [IntRange]
-> FieldAccessor KeySharedMeta IntRange
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "hashRanges" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"hashRanges")) ::
Data.ProtoLens.FieldDescriptor KeySharedMeta
allowOutOfOrderDelivery__field_descriptor :: FieldDescriptor KeySharedMeta
allowOutOfOrderDelivery__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor KeySharedMeta Bool
-> FieldDescriptor KeySharedMeta
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"allowOutOfOrderDelivery"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens KeySharedMeta KeySharedMeta (Maybe Bool) (Maybe Bool)
-> FieldAccessor KeySharedMeta Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'allowOutOfOrderDelivery" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'allowOutOfOrderDelivery")) ::
Data.ProtoLens.FieldDescriptor KeySharedMeta
in
[(Tag, FieldDescriptor KeySharedMeta)]
-> Map Tag (FieldDescriptor KeySharedMeta)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor KeySharedMeta
keySharedMode__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor KeySharedMeta
hashRanges__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor KeySharedMeta
allowOutOfOrderDelivery__field_descriptor)]
unknownFields :: LensLike' f KeySharedMeta FieldSet
unknownFields
= (KeySharedMeta -> FieldSet)
-> (KeySharedMeta -> FieldSet -> KeySharedMeta)
-> Lens' KeySharedMeta FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeySharedMeta -> FieldSet
_KeySharedMeta'_unknownFields
(\ x__ :: KeySharedMeta
x__ y__ :: FieldSet
y__ -> KeySharedMeta
x__ {_KeySharedMeta'_unknownFields :: FieldSet
_KeySharedMeta'_unknownFields = FieldSet
y__})
defMessage :: KeySharedMeta
defMessage
= $WKeySharedMeta'_constructor :: KeySharedMode
-> Vector IntRange -> Maybe Bool -> FieldSet -> KeySharedMeta
KeySharedMeta'_constructor
{_KeySharedMeta'keySharedMode :: KeySharedMode
_KeySharedMeta'keySharedMode = KeySharedMode
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_KeySharedMeta'hashRanges :: Vector IntRange
_KeySharedMeta'hashRanges = Vector IntRange
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_KeySharedMeta'allowOutOfOrderDelivery :: Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_KeySharedMeta'_unknownFields :: FieldSet
_KeySharedMeta'_unknownFields = []}
parseMessage :: Parser KeySharedMeta
parseMessage
= let
loop ::
KeySharedMeta
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld IntRange
-> Data.ProtoLens.Encoding.Bytes.Parser KeySharedMeta
loop :: KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop x :: KeySharedMeta
x required'keySharedMode :: Bool
required'keySharedMode mutable'hashRanges :: Growing Vector RealWorld IntRange
mutable'hashRanges
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector IntRange
frozen'hashRanges <- IO (Vector IntRange) -> Parser (Vector IntRange)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) IntRange -> IO (Vector IntRange)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld IntRange
Growing Vector (PrimState IO) IntRange
mutable'hashRanges)
(let
missing :: [String]
missing
= (if Bool
required'keySharedMode then
(:) "keySharedMode"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
KeySharedMeta -> Parser KeySharedMeta
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter KeySharedMeta KeySharedMeta FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeySharedMeta -> KeySharedMeta
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeySharedMeta KeySharedMeta FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
KeySharedMeta KeySharedMeta (Vector IntRange) (Vector IntRange)
-> Vector IntRange -> KeySharedMeta -> KeySharedMeta
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'hashRanges" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'hashRanges")
Vector IntRange
frozen'hashRanges
KeySharedMeta
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do KeySharedMode
y <- Parser KeySharedMode -> String -> Parser KeySharedMode
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> KeySharedMode) -> Parser Int -> Parser KeySharedMode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> KeySharedMode
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"keySharedMode"
KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop
(Setter KeySharedMeta KeySharedMeta KeySharedMode KeySharedMode
-> KeySharedMode -> KeySharedMeta -> KeySharedMeta
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "keySharedMode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"keySharedMode") KeySharedMode
y KeySharedMeta
x)
Bool
Prelude.False
Growing Vector RealWorld IntRange
mutable'hashRanges
26
-> do !IntRange
y <- Parser IntRange -> String -> Parser IntRange
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser IntRange -> Parser IntRange
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser IntRange
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"hashRanges"
Growing Vector RealWorld IntRange
v <- IO (Growing Vector RealWorld IntRange)
-> Parser (Growing Vector RealWorld IntRange)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) IntRange
-> IntRange -> IO (Growing Vector (PrimState IO) IntRange)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld IntRange
Growing Vector (PrimState IO) IntRange
mutable'hashRanges IntRange
y)
KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop KeySharedMeta
x Bool
required'keySharedMode Growing Vector RealWorld IntRange
v
32
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"allowOutOfOrderDelivery"
KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop
(Setter KeySharedMeta KeySharedMeta Bool Bool
-> Bool -> KeySharedMeta -> KeySharedMeta
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "allowOutOfOrderDelivery" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"allowOutOfOrderDelivery") Bool
y KeySharedMeta
x)
Bool
required'keySharedMode
Growing Vector RealWorld IntRange
mutable'hashRanges
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop
(Setter KeySharedMeta KeySharedMeta FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeySharedMeta -> KeySharedMeta
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeySharedMeta KeySharedMeta FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) KeySharedMeta
x)
Bool
required'keySharedMode
Growing Vector RealWorld IntRange
mutable'hashRanges
in
Parser KeySharedMeta -> String -> Parser KeySharedMeta
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld IntRange
mutable'hashRanges <- IO (Growing Vector RealWorld IntRange)
-> Parser (Growing Vector RealWorld IntRange)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld IntRange)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
KeySharedMeta
-> Bool
-> Growing Vector RealWorld IntRange
-> Parser KeySharedMeta
loop KeySharedMeta
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld IntRange
mutable'hashRanges)
"KeySharedMeta"
buildMessage :: KeySharedMeta -> Builder
buildMessage
= \ _x :: KeySharedMeta
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
((Int -> Builder)
-> (KeySharedMode -> Int) -> KeySharedMode -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
KeySharedMode -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike
KeySharedMode
KeySharedMeta
KeySharedMeta
KeySharedMode
KeySharedMode
-> KeySharedMeta -> KeySharedMode
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "keySharedMode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"keySharedMode") KeySharedMeta
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((IntRange -> Builder) -> Vector IntRange -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: IntRange
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((ByteString -> Builder)
-> (IntRange -> ByteString) -> IntRange -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
IntRange -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
IntRange
_v))
(FoldLike
(Vector IntRange)
KeySharedMeta
KeySharedMeta
(Vector IntRange)
(Vector IntRange)
-> KeySharedMeta -> Vector IntRange
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'hashRanges" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'hashRanges") KeySharedMeta
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool) KeySharedMeta KeySharedMeta (Maybe Bool) (Maybe Bool)
-> KeySharedMeta -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'allowOutOfOrderDelivery" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'allowOutOfOrderDelivery") KeySharedMeta
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet KeySharedMeta KeySharedMeta FieldSet FieldSet
-> KeySharedMeta -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet KeySharedMeta KeySharedMeta FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields KeySharedMeta
_x))))
instance Control.DeepSeq.NFData KeySharedMeta where
rnf :: KeySharedMeta -> ()
rnf
= \ x__ :: KeySharedMeta
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeySharedMeta -> FieldSet
_KeySharedMeta'_unknownFields KeySharedMeta
x__)
(KeySharedMode -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeySharedMeta -> KeySharedMode
_KeySharedMeta'keySharedMode KeySharedMeta
x__)
(Vector IntRange -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeySharedMeta -> Vector IntRange
_KeySharedMeta'hashRanges KeySharedMeta
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeySharedMeta -> Maybe Bool
_KeySharedMeta'allowOutOfOrderDelivery KeySharedMeta
x__) ())))
data KeySharedMode
= AUTO_SPLIT | STICKY
deriving stock (Int -> KeySharedMode -> ShowS
[KeySharedMode] -> ShowS
KeySharedMode -> String
(Int -> KeySharedMode -> ShowS)
-> (KeySharedMode -> String)
-> ([KeySharedMode] -> ShowS)
-> Show KeySharedMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeySharedMode] -> ShowS
$cshowList :: [KeySharedMode] -> ShowS
show :: KeySharedMode -> String
$cshow :: KeySharedMode -> String
showsPrec :: Int -> KeySharedMode -> ShowS
$cshowsPrec :: Int -> KeySharedMode -> ShowS
Prelude.Show, KeySharedMode -> KeySharedMode -> Bool
(KeySharedMode -> KeySharedMode -> Bool)
-> (KeySharedMode -> KeySharedMode -> Bool) -> Eq KeySharedMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeySharedMode -> KeySharedMode -> Bool
$c/= :: KeySharedMode -> KeySharedMode -> Bool
== :: KeySharedMode -> KeySharedMode -> Bool
$c== :: KeySharedMode -> KeySharedMode -> Bool
Prelude.Eq, Eq KeySharedMode
Eq KeySharedMode =>
(KeySharedMode -> KeySharedMode -> Ordering)
-> (KeySharedMode -> KeySharedMode -> Bool)
-> (KeySharedMode -> KeySharedMode -> Bool)
-> (KeySharedMode -> KeySharedMode -> Bool)
-> (KeySharedMode -> KeySharedMode -> Bool)
-> (KeySharedMode -> KeySharedMode -> KeySharedMode)
-> (KeySharedMode -> KeySharedMode -> KeySharedMode)
-> Ord KeySharedMode
KeySharedMode -> KeySharedMode -> Bool
KeySharedMode -> KeySharedMode -> Ordering
KeySharedMode -> KeySharedMode -> KeySharedMode
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeySharedMode -> KeySharedMode -> KeySharedMode
$cmin :: KeySharedMode -> KeySharedMode -> KeySharedMode
max :: KeySharedMode -> KeySharedMode -> KeySharedMode
$cmax :: KeySharedMode -> KeySharedMode -> KeySharedMode
>= :: KeySharedMode -> KeySharedMode -> Bool
$c>= :: KeySharedMode -> KeySharedMode -> Bool
> :: KeySharedMode -> KeySharedMode -> Bool
$c> :: KeySharedMode -> KeySharedMode -> Bool
<= :: KeySharedMode -> KeySharedMode -> Bool
$c<= :: KeySharedMode -> KeySharedMode -> Bool
< :: KeySharedMode -> KeySharedMode -> Bool
$c< :: KeySharedMode -> KeySharedMode -> Bool
compare :: KeySharedMode -> KeySharedMode -> Ordering
$ccompare :: KeySharedMode -> KeySharedMode -> Ordering
$cp1Ord :: Eq KeySharedMode
Prelude.Ord)
instance Data.ProtoLens.MessageEnum KeySharedMode where
maybeToEnum :: Int -> Maybe KeySharedMode
maybeToEnum 0 = KeySharedMode -> Maybe KeySharedMode
forall a. a -> Maybe a
Prelude.Just KeySharedMode
AUTO_SPLIT
maybeToEnum 1 = KeySharedMode -> Maybe KeySharedMode
forall a. a -> Maybe a
Prelude.Just KeySharedMode
STICKY
maybeToEnum _ = Maybe KeySharedMode
forall a. Maybe a
Prelude.Nothing
showEnum :: KeySharedMode -> String
showEnum AUTO_SPLIT = "AUTO_SPLIT"
showEnum STICKY = "STICKY"
readEnum :: String -> Maybe KeySharedMode
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AUTO_SPLIT" = KeySharedMode -> Maybe KeySharedMode
forall a. a -> Maybe a
Prelude.Just KeySharedMode
AUTO_SPLIT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "STICKY" = KeySharedMode -> Maybe KeySharedMode
forall a. a -> Maybe a
Prelude.Just KeySharedMode
STICKY
| Bool
Prelude.otherwise
= Maybe Int -> (Int -> Maybe KeySharedMode) -> Maybe KeySharedMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe KeySharedMode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded KeySharedMode where
minBound :: KeySharedMode
minBound = KeySharedMode
AUTO_SPLIT
maxBound :: KeySharedMode
maxBound = KeySharedMode
STICKY
instance Prelude.Enum KeySharedMode where
toEnum :: Int -> KeySharedMode
toEnum k__ :: Int
k__
= KeySharedMode
-> (KeySharedMode -> KeySharedMode)
-> Maybe KeySharedMode
-> KeySharedMode
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> KeySharedMode
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum KeySharedMode: "
(Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
KeySharedMode -> KeySharedMode
forall a. a -> a
Prelude.id
(Int -> Maybe KeySharedMode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: KeySharedMode -> Int
fromEnum AUTO_SPLIT = 0
fromEnum STICKY = 1
succ :: KeySharedMode -> KeySharedMode
succ STICKY
= String -> KeySharedMode
forall a. HasCallStack => String -> a
Prelude.error
"KeySharedMode.succ: bad argument STICKY. This value would be out of bounds."
succ AUTO_SPLIT = KeySharedMode
STICKY
pred :: KeySharedMode -> KeySharedMode
pred AUTO_SPLIT
= String -> KeySharedMode
forall a. HasCallStack => String -> a
Prelude.error
"KeySharedMode.pred: bad argument AUTO_SPLIT. This value would be out of bounds."
pred STICKY = KeySharedMode
AUTO_SPLIT
enumFrom :: KeySharedMode -> [KeySharedMode]
enumFrom = KeySharedMode -> [KeySharedMode]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: KeySharedMode -> KeySharedMode -> [KeySharedMode]
enumFromTo = KeySharedMode -> KeySharedMode -> [KeySharedMode]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: KeySharedMode -> KeySharedMode -> [KeySharedMode]
enumFromThen = KeySharedMode -> KeySharedMode -> [KeySharedMode]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: KeySharedMode -> KeySharedMode -> KeySharedMode -> [KeySharedMode]
enumFromThenTo = KeySharedMode -> KeySharedMode -> KeySharedMode -> [KeySharedMode]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault KeySharedMode where
fieldDefault :: KeySharedMode
fieldDefault = KeySharedMode
AUTO_SPLIT
instance Control.DeepSeq.NFData KeySharedMode where
rnf :: KeySharedMode -> ()
rnf x__ :: KeySharedMode
x__ = KeySharedMode -> () -> ()
forall a b. a -> b -> b
Prelude.seq KeySharedMode
x__ ()
data KeyValue
= KeyValue'_constructor {KeyValue -> Text
_KeyValue'key :: !Data.Text.Text,
KeyValue -> Text
_KeyValue'value :: !Data.Text.Text,
KeyValue -> FieldSet
_KeyValue'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (KeyValue -> KeyValue -> Bool
(KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool) -> Eq KeyValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyValue -> KeyValue -> Bool
$c/= :: KeyValue -> KeyValue -> Bool
== :: KeyValue -> KeyValue -> Bool
$c== :: KeyValue -> KeyValue -> Bool
Prelude.Eq, Eq KeyValue
Eq KeyValue =>
(KeyValue -> KeyValue -> Ordering)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> Bool)
-> (KeyValue -> KeyValue -> KeyValue)
-> (KeyValue -> KeyValue -> KeyValue)
-> Ord KeyValue
KeyValue -> KeyValue -> Bool
KeyValue -> KeyValue -> Ordering
KeyValue -> KeyValue -> KeyValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeyValue -> KeyValue -> KeyValue
$cmin :: KeyValue -> KeyValue -> KeyValue
max :: KeyValue -> KeyValue -> KeyValue
$cmax :: KeyValue -> KeyValue -> KeyValue
>= :: KeyValue -> KeyValue -> Bool
$c>= :: KeyValue -> KeyValue -> Bool
> :: KeyValue -> KeyValue -> Bool
$c> :: KeyValue -> KeyValue -> Bool
<= :: KeyValue -> KeyValue -> Bool
$c<= :: KeyValue -> KeyValue -> Bool
< :: KeyValue -> KeyValue -> Bool
$c< :: KeyValue -> KeyValue -> Bool
compare :: KeyValue -> KeyValue -> Ordering
$ccompare :: KeyValue -> KeyValue -> Ordering
$cp1Ord :: Eq KeyValue
Prelude.Ord)
instance Prelude.Show KeyValue where
showsPrec :: Int -> KeyValue -> ShowS
showsPrec _ __x :: KeyValue
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(KeyValue -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort KeyValue
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField KeyValue "key" Data.Text.Text where
fieldOf :: Proxy# "key" -> (Text -> f Text) -> KeyValue -> f KeyValue
fieldOf _
= ((Text -> f Text) -> KeyValue -> f KeyValue)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> KeyValue
-> f KeyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeyValue -> Text)
-> (KeyValue -> Text -> KeyValue)
-> Lens KeyValue KeyValue Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyValue -> Text
_KeyValue'key (\ x__ :: KeyValue
x__ y__ :: Text
y__ -> KeyValue
x__ {_KeyValue'key :: Text
_KeyValue'key = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField KeyValue "value" Data.Text.Text where
fieldOf :: Proxy# "value" -> (Text -> f Text) -> KeyValue -> f KeyValue
fieldOf _
= ((Text -> f Text) -> KeyValue -> f KeyValue)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> KeyValue
-> f KeyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((KeyValue -> Text)
-> (KeyValue -> Text -> KeyValue)
-> Lens KeyValue KeyValue Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyValue -> Text
_KeyValue'value (\ x__ :: KeyValue
x__ y__ :: Text
y__ -> KeyValue
x__ {_KeyValue'value :: Text
_KeyValue'value = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message KeyValue where
messageName :: Proxy KeyValue -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.KeyValue"
packedMessageDescriptor :: Proxy KeyValue -> ByteString
packedMessageDescriptor _
= "\n\
\\bKeyValue\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\tR\ENQvalue"
packedFileDescriptor :: Proxy KeyValue -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor KeyValue)
fieldsByTag
= let
key__field_descriptor :: FieldDescriptor KeyValue
key__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor KeyValue Text
-> FieldDescriptor KeyValue
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"key"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens KeyValue KeyValue Text Text -> FieldAccessor KeyValue Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key")) ::
Data.ProtoLens.FieldDescriptor KeyValue
value__field_descriptor :: FieldDescriptor KeyValue
value__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor KeyValue Text
-> FieldDescriptor KeyValue
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"value"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens KeyValue KeyValue Text Text -> FieldAccessor KeyValue Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value")) ::
Data.ProtoLens.FieldDescriptor KeyValue
in
[(Tag, FieldDescriptor KeyValue)]
-> Map Tag (FieldDescriptor KeyValue)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor KeyValue
key__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor KeyValue
value__field_descriptor)]
unknownFields :: LensLike' f KeyValue FieldSet
unknownFields
= (KeyValue -> FieldSet)
-> (KeyValue -> FieldSet -> KeyValue) -> Lens' KeyValue FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
KeyValue -> FieldSet
_KeyValue'_unknownFields
(\ x__ :: KeyValue
x__ y__ :: FieldSet
y__ -> KeyValue
x__ {_KeyValue'_unknownFields :: FieldSet
_KeyValue'_unknownFields = FieldSet
y__})
defMessage :: KeyValue
defMessage
= $WKeyValue'_constructor :: Text -> Text -> FieldSet -> KeyValue
KeyValue'_constructor
{_KeyValue'key :: Text
_KeyValue'key = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_KeyValue'value :: Text
_KeyValue'value = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_KeyValue'_unknownFields :: FieldSet
_KeyValue'_unknownFields = []}
parseMessage :: Parser KeyValue
parseMessage
= let
loop ::
KeyValue
-> Prelude.Bool
-> Prelude.Bool -> Data.ProtoLens.Encoding.Bytes.Parser KeyValue
loop :: KeyValue -> Bool -> Bool -> Parser KeyValue
loop x :: KeyValue
x required'key :: Bool
required'key required'value :: Bool
required'value
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'key then (:) "key" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'value then (:) "value" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
KeyValue -> Parser KeyValue
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter KeyValue KeyValue FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeyValue -> KeyValue
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeyValue KeyValue FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) KeyValue
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"key"
KeyValue -> Bool -> Bool -> Parser KeyValue
loop
(Setter KeyValue KeyValue Text Text -> Text -> KeyValue -> KeyValue
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") Text
y KeyValue
x)
Bool
Prelude.False
Bool
required'value
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"value"
KeyValue -> Bool -> Bool -> Parser KeyValue
loop
(Setter KeyValue KeyValue Text Text -> Text -> KeyValue -> KeyValue
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") Text
y KeyValue
x)
Bool
required'key
Bool
Prelude.False
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
KeyValue -> Bool -> Bool -> Parser KeyValue
loop
(Setter KeyValue KeyValue FieldSet FieldSet
-> (FieldSet -> FieldSet) -> KeyValue -> KeyValue
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter KeyValue KeyValue FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) KeyValue
x)
Bool
required'key
Bool
required'value
in
Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do KeyValue -> Bool -> Bool -> Parser KeyValue
loop KeyValue
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"KeyValue"
buildMessage :: KeyValue -> Builder
buildMessage
= \ _x :: KeyValue
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text KeyValue KeyValue Text Text -> KeyValue -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "key" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"key") KeyValue
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text KeyValue KeyValue Text Text -> KeyValue -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "value" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"value") KeyValue
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet KeyValue KeyValue FieldSet FieldSet
-> KeyValue -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet KeyValue KeyValue FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields KeyValue
_x)))
instance Control.DeepSeq.NFData KeyValue where
rnf :: KeyValue -> ()
rnf
= \ x__ :: KeyValue
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeyValue -> FieldSet
_KeyValue'_unknownFields KeyValue
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(KeyValue -> Text
_KeyValue'key KeyValue
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (KeyValue -> Text
_KeyValue'value KeyValue
x__) ()))
data MessageIdData
= MessageIdData'_constructor {MessageIdData -> Word64
_MessageIdData'ledgerId :: !Data.Word.Word64,
MessageIdData -> Word64
_MessageIdData'entryId :: !Data.Word.Word64,
MessageIdData -> Maybe Int32
_MessageIdData'partition :: !(Prelude.Maybe Data.Int.Int32),
MessageIdData -> Maybe Int32
_MessageIdData'batchIndex :: !(Prelude.Maybe Data.Int.Int32),
MessageIdData -> Vector Int64
_MessageIdData'ackSet :: !(Data.Vector.Unboxed.Vector Data.Int.Int64),
MessageIdData -> FieldSet
_MessageIdData'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (MessageIdData -> MessageIdData -> Bool
(MessageIdData -> MessageIdData -> Bool)
-> (MessageIdData -> MessageIdData -> Bool) -> Eq MessageIdData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageIdData -> MessageIdData -> Bool
$c/= :: MessageIdData -> MessageIdData -> Bool
== :: MessageIdData -> MessageIdData -> Bool
$c== :: MessageIdData -> MessageIdData -> Bool
Prelude.Eq, Eq MessageIdData
Eq MessageIdData =>
(MessageIdData -> MessageIdData -> Ordering)
-> (MessageIdData -> MessageIdData -> Bool)
-> (MessageIdData -> MessageIdData -> Bool)
-> (MessageIdData -> MessageIdData -> Bool)
-> (MessageIdData -> MessageIdData -> Bool)
-> (MessageIdData -> MessageIdData -> MessageIdData)
-> (MessageIdData -> MessageIdData -> MessageIdData)
-> Ord MessageIdData
MessageIdData -> MessageIdData -> Bool
MessageIdData -> MessageIdData -> Ordering
MessageIdData -> MessageIdData -> MessageIdData
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MessageIdData -> MessageIdData -> MessageIdData
$cmin :: MessageIdData -> MessageIdData -> MessageIdData
max :: MessageIdData -> MessageIdData -> MessageIdData
$cmax :: MessageIdData -> MessageIdData -> MessageIdData
>= :: MessageIdData -> MessageIdData -> Bool
$c>= :: MessageIdData -> MessageIdData -> Bool
> :: MessageIdData -> MessageIdData -> Bool
$c> :: MessageIdData -> MessageIdData -> Bool
<= :: MessageIdData -> MessageIdData -> Bool
$c<= :: MessageIdData -> MessageIdData -> Bool
< :: MessageIdData -> MessageIdData -> Bool
$c< :: MessageIdData -> MessageIdData -> Bool
compare :: MessageIdData -> MessageIdData -> Ordering
$ccompare :: MessageIdData -> MessageIdData -> Ordering
$cp1Ord :: Eq MessageIdData
Prelude.Ord)
instance Prelude.Show MessageIdData where
showsPrec :: Int -> MessageIdData -> ShowS
showsPrec _ __x :: MessageIdData
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(MessageIdData -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort MessageIdData
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField MessageIdData "ledgerId" Data.Word.Word64 where
fieldOf :: Proxy# "ledgerId"
-> (Word64 -> f Word64) -> MessageIdData -> f MessageIdData
fieldOf _
= ((Word64 -> f Word64) -> MessageIdData -> f MessageIdData)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Word64)
-> (MessageIdData -> Word64 -> MessageIdData)
-> Lens MessageIdData MessageIdData Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Word64
_MessageIdData'ledgerId
(\ x__ :: MessageIdData
x__ y__ :: Word64
y__ -> MessageIdData
x__ {_MessageIdData'ledgerId :: Word64
_MessageIdData'ledgerId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageIdData "entryId" Data.Word.Word64 where
fieldOf :: Proxy# "entryId"
-> (Word64 -> f Word64) -> MessageIdData -> f MessageIdData
fieldOf _
= ((Word64 -> f Word64) -> MessageIdData -> f MessageIdData)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Word64)
-> (MessageIdData -> Word64 -> MessageIdData)
-> Lens MessageIdData MessageIdData Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Word64
_MessageIdData'entryId
(\ x__ :: MessageIdData
x__ y__ :: Word64
y__ -> MessageIdData
x__ {_MessageIdData'entryId :: Word64
_MessageIdData'entryId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageIdData "partition" Data.Int.Int32 where
fieldOf :: Proxy# "partition"
-> (Int32 -> f Int32) -> MessageIdData -> f MessageIdData
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageIdData -> f MessageIdData)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Maybe Int32)
-> (MessageIdData -> Maybe Int32 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Maybe Int32
_MessageIdData'partition
(\ x__ :: MessageIdData
x__ y__ :: Maybe Int32
y__ -> MessageIdData
x__ {_MessageIdData'partition :: Maybe Int32
_MessageIdData'partition = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens (-1))
instance Data.ProtoLens.Field.HasField MessageIdData "maybe'partition" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'partition"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageIdData
-> f MessageIdData
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageIdData -> f MessageIdData)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Maybe Int32)
-> (MessageIdData -> Maybe Int32 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Maybe Int32
_MessageIdData'partition
(\ x__ :: MessageIdData
x__ y__ :: Maybe Int32
y__ -> MessageIdData
x__ {_MessageIdData'partition :: Maybe Int32
_MessageIdData'partition = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageIdData "batchIndex" Data.Int.Int32 where
fieldOf :: Proxy# "batchIndex"
-> (Int32 -> f Int32) -> MessageIdData -> f MessageIdData
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageIdData -> f MessageIdData)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Maybe Int32)
-> (MessageIdData -> Maybe Int32 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Maybe Int32
_MessageIdData'batchIndex
(\ x__ :: MessageIdData
x__ y__ :: Maybe Int32
y__ -> MessageIdData
x__ {_MessageIdData'batchIndex :: Maybe Int32
_MessageIdData'batchIndex = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens (-1))
instance Data.ProtoLens.Field.HasField MessageIdData "maybe'batchIndex" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'batchIndex"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageIdData
-> f MessageIdData
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageIdData -> f MessageIdData)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Maybe Int32)
-> (MessageIdData -> Maybe Int32 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Maybe Int32
_MessageIdData'batchIndex
(\ x__ :: MessageIdData
x__ y__ :: Maybe Int32
y__ -> MessageIdData
x__ {_MessageIdData'batchIndex :: Maybe Int32
_MessageIdData'batchIndex = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageIdData "ackSet" [Data.Int.Int64] where
fieldOf :: Proxy# "ackSet"
-> ([Int64] -> f [Int64]) -> MessageIdData -> f MessageIdData
fieldOf _
= ((Vector Int64 -> f (Vector Int64))
-> MessageIdData -> f MessageIdData)
-> (([Int64] -> f [Int64]) -> Vector Int64 -> f (Vector Int64))
-> ([Int64] -> f [Int64])
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Vector Int64)
-> (MessageIdData -> Vector Int64 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Vector Int64) (Vector Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Vector Int64
_MessageIdData'ackSet
(\ x__ :: MessageIdData
x__ y__ :: Vector Int64
y__ -> MessageIdData
x__ {_MessageIdData'ackSet :: Vector Int64
_MessageIdData'ackSet = Vector Int64
y__}))
((Vector Int64 -> [Int64])
-> (Vector Int64 -> [Int64] -> Vector Int64)
-> Lens (Vector Int64) (Vector Int64) [Int64] [Int64]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Int64 -> [Int64]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Int64]
y__ -> [Int64] -> Vector Int64
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Int64]
y__))
instance Data.ProtoLens.Field.HasField MessageIdData "vec'ackSet" (Data.Vector.Unboxed.Vector Data.Int.Int64) where
fieldOf :: Proxy# "vec'ackSet"
-> (Vector Int64 -> f (Vector Int64))
-> MessageIdData
-> f MessageIdData
fieldOf _
= ((Vector Int64 -> f (Vector Int64))
-> MessageIdData -> f MessageIdData)
-> ((Vector Int64 -> f (Vector Int64))
-> Vector Int64 -> f (Vector Int64))
-> (Vector Int64 -> f (Vector Int64))
-> MessageIdData
-> f MessageIdData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageIdData -> Vector Int64)
-> (MessageIdData -> Vector Int64 -> MessageIdData)
-> Lens MessageIdData MessageIdData (Vector Int64) (Vector Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> Vector Int64
_MessageIdData'ackSet
(\ x__ :: MessageIdData
x__ y__ :: Vector Int64
y__ -> MessageIdData
x__ {_MessageIdData'ackSet :: Vector Int64
_MessageIdData'ackSet = Vector Int64
y__}))
(Vector Int64 -> f (Vector Int64))
-> Vector Int64 -> f (Vector Int64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message MessageIdData where
messageName :: Proxy MessageIdData -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.MessageIdData"
packedMessageDescriptor :: Proxy MessageIdData -> ByteString
packedMessageDescriptor _
= "\n\
\\rMessageIdData\DC2\SUB\n\
\\bledgerId\CAN\SOH \STX(\EOTR\bledgerId\DC2\CAN\n\
\\aentryId\CAN\STX \STX(\EOTR\aentryId\DC2 \n\
\\tpartition\CAN\ETX \SOH(\ENQ:\STX-1R\tpartition\DC2#\n\
\\vbatch_index\CAN\EOT \SOH(\ENQ:\STX-1R\n\
\batchIndex\DC2\ETB\n\
\\aack_set\CAN\ENQ \ETX(\ETXR\ACKackSet"
packedFileDescriptor :: Proxy MessageIdData -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor MessageIdData)
fieldsByTag
= let
ledgerId__field_descriptor :: FieldDescriptor MessageIdData
ledgerId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageIdData Word64
-> FieldDescriptor MessageIdData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ledgerId"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens MessageIdData MessageIdData Word64 Word64
-> FieldAccessor MessageIdData Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "ledgerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ledgerId")) ::
Data.ProtoLens.FieldDescriptor MessageIdData
entryId__field_descriptor :: FieldDescriptor MessageIdData
entryId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageIdData Word64
-> FieldDescriptor MessageIdData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"entryId"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens MessageIdData MessageIdData Word64 Word64
-> FieldAccessor MessageIdData Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "entryId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"entryId")) ::
Data.ProtoLens.FieldDescriptor MessageIdData
partition__field_descriptor :: FieldDescriptor MessageIdData
partition__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageIdData Int32
-> FieldDescriptor MessageIdData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partition"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageIdData Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partition")) ::
Data.ProtoLens.FieldDescriptor MessageIdData
batchIndex__field_descriptor :: FieldDescriptor MessageIdData
batchIndex__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageIdData Int32
-> FieldDescriptor MessageIdData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"batch_index"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageIdData MessageIdData (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageIdData Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'batchIndex" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'batchIndex")) ::
Data.ProtoLens.FieldDescriptor MessageIdData
ackSet__field_descriptor :: FieldDescriptor MessageIdData
ackSet__field_descriptor
= String
-> FieldTypeDescriptor Int64
-> FieldAccessor MessageIdData Int64
-> FieldDescriptor MessageIdData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ack_set"
(ScalarField Int64 -> FieldTypeDescriptor Int64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int64
Data.ProtoLens.Int64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int64)
(Packing
-> Lens' MessageIdData [Int64] -> FieldAccessor MessageIdData Int64
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ackSet")) ::
Data.ProtoLens.FieldDescriptor MessageIdData
in
[(Tag, FieldDescriptor MessageIdData)]
-> Map Tag (FieldDescriptor MessageIdData)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor MessageIdData
ledgerId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor MessageIdData
entryId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor MessageIdData
partition__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor MessageIdData
batchIndex__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor MessageIdData
ackSet__field_descriptor)]
unknownFields :: LensLike' f MessageIdData FieldSet
unknownFields
= (MessageIdData -> FieldSet)
-> (MessageIdData -> FieldSet -> MessageIdData)
-> Lens' MessageIdData FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageIdData -> FieldSet
_MessageIdData'_unknownFields
(\ x__ :: MessageIdData
x__ y__ :: FieldSet
y__ -> MessageIdData
x__ {_MessageIdData'_unknownFields :: FieldSet
_MessageIdData'_unknownFields = FieldSet
y__})
defMessage :: MessageIdData
defMessage
= $WMessageIdData'_constructor :: Word64
-> Word64
-> Maybe Int32
-> Maybe Int32
-> Vector Int64
-> FieldSet
-> MessageIdData
MessageIdData'_constructor
{_MessageIdData'ledgerId :: Word64
_MessageIdData'ledgerId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_MessageIdData'entryId :: Word64
_MessageIdData'entryId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_MessageIdData'partition :: Maybe Int32
_MessageIdData'partition = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageIdData'batchIndex :: Maybe Int32
_MessageIdData'batchIndex = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageIdData'ackSet :: Vector Int64
_MessageIdData'ackSet = Vector Int64
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_MessageIdData'_unknownFields :: FieldSet
_MessageIdData'_unknownFields = []}
parseMessage :: Parser MessageIdData
parseMessage
= let
loop ::
MessageIdData
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Unboxed.Vector Data.ProtoLens.Encoding.Growing.RealWorld Data.Int.Int64
-> Data.ProtoLens.Encoding.Bytes.Parser MessageIdData
loop :: MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop x :: MessageIdData
x required'entryId :: Bool
required'entryId required'ledgerId :: Bool
required'ledgerId mutable'ackSet :: Growing Vector RealWorld Int64
mutable'ackSet
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector Int64
frozen'ackSet <- IO (Vector Int64) -> Parser (Vector Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Int64 -> IO (Vector Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Int64
Growing Vector (PrimState IO) Int64
mutable'ackSet)
(let
missing :: [String]
missing
= (if Bool
required'entryId then (:) "entryId" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'ledgerId then (:) "ledgerId" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
MessageIdData -> Parser MessageIdData
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter MessageIdData MessageIdData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter MessageIdData MessageIdData FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter MessageIdData MessageIdData (Vector Int64) (Vector Int64)
-> Vector Int64 -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ackSet") Vector Int64
frozen'ackSet MessageIdData
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
8 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "ledgerId"
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
(Setter MessageIdData MessageIdData Word64 Word64
-> Word64 -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "ledgerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ledgerId") Word64
y MessageIdData
x)
Bool
required'entryId
Bool
Prelude.False
Growing Vector RealWorld Int64
mutable'ackSet
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "entryId"
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
(Setter MessageIdData MessageIdData Word64 Word64
-> Word64 -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "entryId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"entryId") Word64
y MessageIdData
x)
Bool
Prelude.False
Bool
required'ledgerId
Growing Vector RealWorld Int64
mutable'ackSet
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"partition"
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
(Setter MessageIdData MessageIdData Int32 Int32
-> Int32 -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "partition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partition") Int32
y MessageIdData
x)
Bool
required'entryId
Bool
required'ledgerId
Growing Vector RealWorld Int64
mutable'ackSet
32
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"batch_index"
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
(Setter MessageIdData MessageIdData Int32 Int32
-> Int32 -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "batchIndex" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"batchIndex") Int32
y MessageIdData
x)
Bool
required'entryId
Bool
required'ledgerId
Growing Vector RealWorld Int64
mutable'ackSet
40
-> do !Int64
y <- Parser Int64 -> String -> Parser Int64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int64) -> Parser Word64 -> Parser Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"ack_set"
Growing Vector RealWorld Int64
v <- IO (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Int64
-> Int64 -> IO (Growing Vector (PrimState IO) Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Int64
Growing Vector (PrimState IO) Int64
mutable'ackSet Int64
y)
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop MessageIdData
x Bool
required'entryId Bool
required'ledgerId Growing Vector RealWorld Int64
v
42
-> do Growing Vector RealWorld Int64
y <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int
-> Parser (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
((let
ploop :: Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop qs :: Growing v RealWorld a
qs
= do Bool
packedEnd <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
packedEnd then
Growing v RealWorld a -> Parser (Growing v RealWorld a)
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return Growing v RealWorld a
qs
else
do !a
q <- Parser a -> String -> Parser a
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> a) -> Parser Word64 -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> a
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"ack_set"
Growing v RealWorld a
qs' <- IO (Growing v RealWorld a) -> Parser (Growing v RealWorld a)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing v (PrimState IO) a -> a -> IO (Growing v (PrimState IO) a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
Growing v RealWorld a
Growing v (PrimState IO) a
qs a
q)
Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop Growing v RealWorld a
qs'
in forall a (v :: * -> *).
(Num a, Vector v a) =>
Growing v RealWorld a -> Parser (Growing v RealWorld a)
ploop)
Growing Vector RealWorld Int64
mutable'ackSet)
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop MessageIdData
x Bool
required'entryId Bool
required'ledgerId Growing Vector RealWorld Int64
y
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
(Setter MessageIdData MessageIdData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> MessageIdData -> MessageIdData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter MessageIdData MessageIdData FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) MessageIdData
x)
Bool
required'entryId
Bool
required'ledgerId
Growing Vector RealWorld Int64
mutable'ackSet
in
Parser MessageIdData -> String -> Parser MessageIdData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld Int64
mutable'ackSet <- IO (Growing Vector RealWorld Int64)
-> Parser (Growing Vector RealWorld Int64)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Int64)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
MessageIdData
-> Bool
-> Bool
-> Growing Vector RealWorld Int64
-> Parser MessageIdData
loop
MessageIdData
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True Growing Vector RealWorld Int64
mutable'ackSet)
"MessageIdData"
buildMessage :: MessageIdData -> Builder
buildMessage
= \ _x :: MessageIdData
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 MessageIdData MessageIdData Word64 Word64
-> MessageIdData -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "ledgerId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ledgerId") MessageIdData
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 MessageIdData MessageIdData Word64 Word64
-> MessageIdData -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "entryId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"entryId") MessageIdData
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageIdData
MessageIdData
(Maybe Int32)
(Maybe Int32)
-> MessageIdData -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partition" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partition") MessageIdData
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageIdData
MessageIdData
(Maybe Int32)
(Maybe Int32)
-> MessageIdData -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'batchIndex" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'batchIndex") MessageIdData
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Int64 -> Builder) -> Vector Int64 -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Int64
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
((Word64 -> Builder) -> (Int64 -> Word64) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int64
_v))
(FoldLike
(Vector Int64)
MessageIdData
MessageIdData
(Vector Int64)
(Vector Int64)
-> MessageIdData -> Vector Int64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "vec'ackSet" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ackSet") MessageIdData
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet MessageIdData MessageIdData FieldSet FieldSet
-> MessageIdData -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet MessageIdData MessageIdData FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields MessageIdData
_x))))))
instance Control.DeepSeq.NFData MessageIdData where
rnf :: MessageIdData -> ()
rnf
= \ x__ :: MessageIdData
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageIdData -> FieldSet
_MessageIdData'_unknownFields MessageIdData
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageIdData -> Word64
_MessageIdData'ledgerId MessageIdData
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageIdData -> Word64
_MessageIdData'entryId MessageIdData
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageIdData -> Maybe Int32
_MessageIdData'partition MessageIdData
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageIdData -> Maybe Int32
_MessageIdData'batchIndex MessageIdData
x__)
(Vector Int64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (MessageIdData -> Vector Int64
_MessageIdData'ackSet MessageIdData
x__) ())))))
data MessageMetadata
= MessageMetadata'_constructor {MessageMetadata -> Text
_MessageMetadata'producerName :: !Data.Text.Text,
MessageMetadata -> Word64
_MessageMetadata'sequenceId :: !Data.Word.Word64,
MessageMetadata -> Word64
_MessageMetadata'publishTime :: !Data.Word.Word64,
MessageMetadata -> Vector KeyValue
_MessageMetadata'properties :: !(Data.Vector.Vector KeyValue),
MessageMetadata -> Maybe Text
_MessageMetadata'replicatedFrom :: !(Prelude.Maybe Data.Text.Text),
MessageMetadata -> Maybe Text
_MessageMetadata'partitionKey :: !(Prelude.Maybe Data.Text.Text),
MessageMetadata -> Vector Text
_MessageMetadata'replicateTo :: !(Data.Vector.Vector Data.Text.Text),
MessageMetadata -> Maybe CompressionType
_MessageMetadata'compression :: !(Prelude.Maybe CompressionType),
MessageMetadata -> Maybe Word32
_MessageMetadata'uncompressedSize :: !(Prelude.Maybe Data.Word.Word32),
MessageMetadata -> Maybe Int32
_MessageMetadata'numMessagesInBatch :: !(Prelude.Maybe Data.Int.Int32),
MessageMetadata -> Maybe Word64
_MessageMetadata'eventTime :: !(Prelude.Maybe Data.Word.Word64),
MessageMetadata -> Vector EncryptionKeys
_MessageMetadata'encryptionKeys :: !(Data.Vector.Vector EncryptionKeys),
MessageMetadata -> Maybe Text
_MessageMetadata'encryptionAlgo :: !(Prelude.Maybe Data.Text.Text),
MessageMetadata -> Maybe ByteString
_MessageMetadata'encryptionParam :: !(Prelude.Maybe Data.ByteString.ByteString),
MessageMetadata -> Maybe ByteString
_MessageMetadata'schemaVersion :: !(Prelude.Maybe Data.ByteString.ByteString),
MessageMetadata -> Maybe Bool
_MessageMetadata'partitionKeyB64Encoded :: !(Prelude.Maybe Prelude.Bool),
MessageMetadata -> Maybe ByteString
_MessageMetadata'orderingKey :: !(Prelude.Maybe Data.ByteString.ByteString),
MessageMetadata -> Maybe Int64
_MessageMetadata'deliverAtTime :: !(Prelude.Maybe Data.Int.Int64),
MessageMetadata -> Maybe Int32
_MessageMetadata'markerType :: !(Prelude.Maybe Data.Int.Int32),
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidLeastBits :: !(Prelude.Maybe Data.Word.Word64),
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidMostBits :: !(Prelude.Maybe Data.Word.Word64),
MessageMetadata -> Maybe Word64
_MessageMetadata'highestSequenceId :: !(Prelude.Maybe Data.Word.Word64),
MessageMetadata -> Maybe Bool
_MessageMetadata'nullValue :: !(Prelude.Maybe Prelude.Bool),
MessageMetadata -> Maybe Text
_MessageMetadata'uuid :: !(Prelude.Maybe Data.Text.Text),
MessageMetadata -> Maybe Int32
_MessageMetadata'numChunksFromMsg :: !(Prelude.Maybe Data.Int.Int32),
MessageMetadata -> Maybe Int32
_MessageMetadata'totalChunkMsgSize :: !(Prelude.Maybe Data.Int.Int32),
MessageMetadata -> Maybe Int32
_MessageMetadata'chunkId :: !(Prelude.Maybe Data.Int.Int32),
MessageMetadata -> Maybe Bool
_MessageMetadata'nullPartitionKey :: !(Prelude.Maybe Prelude.Bool),
MessageMetadata -> FieldSet
_MessageMetadata'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (MessageMetadata -> MessageMetadata -> Bool
(MessageMetadata -> MessageMetadata -> Bool)
-> (MessageMetadata -> MessageMetadata -> Bool)
-> Eq MessageMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageMetadata -> MessageMetadata -> Bool
$c/= :: MessageMetadata -> MessageMetadata -> Bool
== :: MessageMetadata -> MessageMetadata -> Bool
$c== :: MessageMetadata -> MessageMetadata -> Bool
Prelude.Eq, Eq MessageMetadata
Eq MessageMetadata =>
(MessageMetadata -> MessageMetadata -> Ordering)
-> (MessageMetadata -> MessageMetadata -> Bool)
-> (MessageMetadata -> MessageMetadata -> Bool)
-> (MessageMetadata -> MessageMetadata -> Bool)
-> (MessageMetadata -> MessageMetadata -> Bool)
-> (MessageMetadata -> MessageMetadata -> MessageMetadata)
-> (MessageMetadata -> MessageMetadata -> MessageMetadata)
-> Ord MessageMetadata
MessageMetadata -> MessageMetadata -> Bool
MessageMetadata -> MessageMetadata -> Ordering
MessageMetadata -> MessageMetadata -> MessageMetadata
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MessageMetadata -> MessageMetadata -> MessageMetadata
$cmin :: MessageMetadata -> MessageMetadata -> MessageMetadata
max :: MessageMetadata -> MessageMetadata -> MessageMetadata
$cmax :: MessageMetadata -> MessageMetadata -> MessageMetadata
>= :: MessageMetadata -> MessageMetadata -> Bool
$c>= :: MessageMetadata -> MessageMetadata -> Bool
> :: MessageMetadata -> MessageMetadata -> Bool
$c> :: MessageMetadata -> MessageMetadata -> Bool
<= :: MessageMetadata -> MessageMetadata -> Bool
$c<= :: MessageMetadata -> MessageMetadata -> Bool
< :: MessageMetadata -> MessageMetadata -> Bool
$c< :: MessageMetadata -> MessageMetadata -> Bool
compare :: MessageMetadata -> MessageMetadata -> Ordering
$ccompare :: MessageMetadata -> MessageMetadata -> Ordering
$cp1Ord :: Eq MessageMetadata
Prelude.Ord)
instance Prelude.Show MessageMetadata where
showsPrec :: Int -> MessageMetadata -> ShowS
showsPrec _ __x :: MessageMetadata
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(MessageMetadata -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort MessageMetadata
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField MessageMetadata "producerName" Data.Text.Text where
fieldOf :: Proxy# "producerName"
-> (Text -> f Text) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Text -> f Text) -> MessageMetadata -> f MessageMetadata)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Text)
-> (MessageMetadata -> Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Text
_MessageMetadata'producerName
(\ x__ :: MessageMetadata
x__ y__ :: Text
y__ -> MessageMetadata
x__ {_MessageMetadata'producerName :: Text
_MessageMetadata'producerName = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "sequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "sequenceId"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Word64)
-> (MessageMetadata -> Word64 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Word64
_MessageMetadata'sequenceId
(\ x__ :: MessageMetadata
x__ y__ :: Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'sequenceId :: Word64
_MessageMetadata'sequenceId = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "publishTime" Data.Word.Word64 where
fieldOf :: Proxy# "publishTime"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Word64)
-> (MessageMetadata -> Word64 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Word64
_MessageMetadata'publishTime
(\ x__ :: MessageMetadata
x__ y__ :: Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'publishTime :: Word64
_MessageMetadata'publishTime = Word64
y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "properties" [KeyValue] where
fieldOf :: Proxy# "properties"
-> ([KeyValue] -> f [KeyValue])
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> MessageMetadata -> f MessageMetadata)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector KeyValue)
-> (MessageMetadata -> Vector KeyValue -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector KeyValue
_MessageMetadata'properties
(\ x__ :: MessageMetadata
x__ y__ :: Vector KeyValue
y__ -> MessageMetadata
x__ {_MessageMetadata'properties :: Vector KeyValue
_MessageMetadata'properties = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField MessageMetadata "vec'properties" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'properties"
-> (Vector KeyValue -> f (Vector KeyValue))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> MessageMetadata -> f MessageMetadata)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector KeyValue)
-> (MessageMetadata -> Vector KeyValue -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector KeyValue
_MessageMetadata'properties
(\ x__ :: MessageMetadata
x__ y__ :: Vector KeyValue
y__ -> MessageMetadata
x__ {_MessageMetadata'properties :: Vector KeyValue
_MessageMetadata'properties = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "replicatedFrom" Data.Text.Text where
fieldOf :: Proxy# "replicatedFrom"
-> (Text -> f Text) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'replicatedFrom
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'replicatedFrom :: Maybe Text
_MessageMetadata'replicatedFrom = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'replicatedFrom" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'replicatedFrom"
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'replicatedFrom
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'replicatedFrom :: Maybe Text
_MessageMetadata'replicatedFrom = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "partitionKey" Data.Text.Text where
fieldOf :: Proxy# "partitionKey"
-> (Text -> f Text) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'partitionKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'partitionKey :: Maybe Text
_MessageMetadata'partitionKey = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'partitionKey" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'partitionKey"
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'partitionKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'partitionKey :: Maybe Text
_MessageMetadata'partitionKey = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "replicateTo" [Data.Text.Text] where
fieldOf :: Proxy# "replicateTo"
-> ([Text] -> f [Text]) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Vector Text -> f (Vector Text))
-> MessageMetadata -> f MessageMetadata)
-> (([Text] -> f [Text]) -> Vector Text -> f (Vector Text))
-> ([Text] -> f [Text])
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector Text)
-> (MessageMetadata -> Vector Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Vector Text) (Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector Text
_MessageMetadata'replicateTo
(\ x__ :: MessageMetadata
x__ y__ :: Vector Text
y__ -> MessageMetadata
x__ {_MessageMetadata'replicateTo :: Vector Text
_MessageMetadata'replicateTo = Vector Text
y__}))
((Vector Text -> [Text])
-> (Vector Text -> [Text] -> Vector Text)
-> Lens (Vector Text) (Vector Text) [Text] [Text]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector Text -> [Text]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [Text]
y__ -> [Text] -> Vector Text
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Text]
y__))
instance Data.ProtoLens.Field.HasField MessageMetadata "vec'replicateTo" (Data.Vector.Vector Data.Text.Text) where
fieldOf :: Proxy# "vec'replicateTo"
-> (Vector Text -> f (Vector Text))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Vector Text -> f (Vector Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Vector Text -> f (Vector Text))
-> Vector Text -> f (Vector Text))
-> (Vector Text -> f (Vector Text))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector Text)
-> (MessageMetadata -> Vector Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Vector Text) (Vector Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector Text
_MessageMetadata'replicateTo
(\ x__ :: MessageMetadata
x__ y__ :: Vector Text
y__ -> MessageMetadata
x__ {_MessageMetadata'replicateTo :: Vector Text
_MessageMetadata'replicateTo = Vector Text
y__}))
(Vector Text -> f (Vector Text)) -> Vector Text -> f (Vector Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "compression" CompressionType where
fieldOf :: Proxy# "compression"
-> (CompressionType -> f CompressionType)
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe CompressionType -> f (Maybe CompressionType))
-> MessageMetadata -> f MessageMetadata)
-> ((CompressionType -> f CompressionType)
-> Maybe CompressionType -> f (Maybe CompressionType))
-> (CompressionType -> f CompressionType)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe CompressionType)
-> (MessageMetadata -> Maybe CompressionType -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe CompressionType)
(Maybe CompressionType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe CompressionType
_MessageMetadata'compression
(\ x__ :: MessageMetadata
x__ y__ :: Maybe CompressionType
y__ -> MessageMetadata
x__ {_MessageMetadata'compression :: Maybe CompressionType
_MessageMetadata'compression = Maybe CompressionType
y__}))
(CompressionType -> Lens' (Maybe CompressionType) CompressionType
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens CompressionType
NONE)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'compression" (Prelude.Maybe CompressionType) where
fieldOf :: Proxy# "maybe'compression"
-> (Maybe CompressionType -> f (Maybe CompressionType))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe CompressionType -> f (Maybe CompressionType))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe CompressionType -> f (Maybe CompressionType))
-> Maybe CompressionType -> f (Maybe CompressionType))
-> (Maybe CompressionType -> f (Maybe CompressionType))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe CompressionType)
-> (MessageMetadata -> Maybe CompressionType -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe CompressionType)
(Maybe CompressionType)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe CompressionType
_MessageMetadata'compression
(\ x__ :: MessageMetadata
x__ y__ :: Maybe CompressionType
y__ -> MessageMetadata
x__ {_MessageMetadata'compression :: Maybe CompressionType
_MessageMetadata'compression = Maybe CompressionType
y__}))
(Maybe CompressionType -> f (Maybe CompressionType))
-> Maybe CompressionType -> f (Maybe CompressionType)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "uncompressedSize" Data.Word.Word32 where
fieldOf :: Proxy# "uncompressedSize"
-> (Word32 -> f Word32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> MessageMetadata -> f MessageMetadata)
-> ((Word32 -> f Word32) -> Maybe Word32 -> f (Maybe Word32))
-> (Word32 -> f Word32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word32)
-> (MessageMetadata -> Maybe Word32 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word32) (Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word32
_MessageMetadata'uncompressedSize
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word32
y__ -> MessageMetadata
x__ {_MessageMetadata'uncompressedSize :: Maybe Word32
_MessageMetadata'uncompressedSize = Maybe Word32
y__}))
(Word32 -> Lens' (Maybe Word32) Word32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'uncompressedSize" (Prelude.Maybe Data.Word.Word32) where
fieldOf :: Proxy# "maybe'uncompressedSize"
-> (Maybe Word32 -> f (Maybe Word32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Word32 -> f (Maybe Word32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32))
-> (Maybe Word32 -> f (Maybe Word32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word32)
-> (MessageMetadata -> Maybe Word32 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word32) (Maybe Word32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word32
_MessageMetadata'uncompressedSize
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word32
y__ -> MessageMetadata
x__ {_MessageMetadata'uncompressedSize :: Maybe Word32
_MessageMetadata'uncompressedSize = Maybe Word32
y__}))
(Maybe Word32 -> f (Maybe Word32))
-> Maybe Word32 -> f (Maybe Word32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "numMessagesInBatch" Data.Int.Int32 where
fieldOf :: Proxy# "numMessagesInBatch"
-> (Int32 -> f Int32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'numMessagesInBatch
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'numMessagesInBatch :: Maybe Int32
_MessageMetadata'numMessagesInBatch = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 1)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'numMessagesInBatch" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'numMessagesInBatch"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'numMessagesInBatch
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'numMessagesInBatch :: Maybe Int32
_MessageMetadata'numMessagesInBatch = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "eventTime" Data.Word.Word64 where
fieldOf :: Proxy# "eventTime"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'eventTime
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'eventTime :: Maybe Word64
_MessageMetadata'eventTime = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'eventTime" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'eventTime"
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'eventTime
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'eventTime :: Maybe Word64
_MessageMetadata'eventTime = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "encryptionKeys" [EncryptionKeys] where
fieldOf :: Proxy# "encryptionKeys"
-> ([EncryptionKeys] -> f [EncryptionKeys])
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> MessageMetadata -> f MessageMetadata)
-> (([EncryptionKeys] -> f [EncryptionKeys])
-> Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> ([EncryptionKeys] -> f [EncryptionKeys])
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector EncryptionKeys)
-> (MessageMetadata -> Vector EncryptionKeys -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Vector EncryptionKeys)
(Vector EncryptionKeys)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector EncryptionKeys
_MessageMetadata'encryptionKeys
(\ x__ :: MessageMetadata
x__ y__ :: Vector EncryptionKeys
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionKeys :: Vector EncryptionKeys
_MessageMetadata'encryptionKeys = Vector EncryptionKeys
y__}))
((Vector EncryptionKeys -> [EncryptionKeys])
-> (Vector EncryptionKeys
-> [EncryptionKeys] -> Vector EncryptionKeys)
-> Lens
(Vector EncryptionKeys)
(Vector EncryptionKeys)
[EncryptionKeys]
[EncryptionKeys]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector EncryptionKeys -> [EncryptionKeys]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [EncryptionKeys]
y__ -> [EncryptionKeys] -> Vector EncryptionKeys
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [EncryptionKeys]
y__))
instance Data.ProtoLens.Field.HasField MessageMetadata "vec'encryptionKeys" (Data.Vector.Vector EncryptionKeys) where
fieldOf :: Proxy# "vec'encryptionKeys"
-> (Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> MessageMetadata -> f MessageMetadata)
-> ((Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> (Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Vector EncryptionKeys)
-> (MessageMetadata -> Vector EncryptionKeys -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Vector EncryptionKeys)
(Vector EncryptionKeys)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Vector EncryptionKeys
_MessageMetadata'encryptionKeys
(\ x__ :: MessageMetadata
x__ y__ :: Vector EncryptionKeys
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionKeys :: Vector EncryptionKeys
_MessageMetadata'encryptionKeys = Vector EncryptionKeys
y__}))
(Vector EncryptionKeys -> f (Vector EncryptionKeys))
-> Vector EncryptionKeys -> f (Vector EncryptionKeys)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "encryptionAlgo" Data.Text.Text where
fieldOf :: Proxy# "encryptionAlgo"
-> (Text -> f Text) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'encryptionAlgo
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionAlgo :: Maybe Text
_MessageMetadata'encryptionAlgo = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'encryptionAlgo" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'encryptionAlgo"
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'encryptionAlgo
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionAlgo :: Maybe Text
_MessageMetadata'encryptionAlgo = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "encryptionParam" Data.ByteString.ByteString where
fieldOf :: Proxy# "encryptionParam"
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'encryptionParam
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionParam :: Maybe ByteString
_MessageMetadata'encryptionParam = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'encryptionParam" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'encryptionParam"
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'encryptionParam
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'encryptionParam :: Maybe ByteString
_MessageMetadata'encryptionParam = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "schemaVersion" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaVersion"
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'schemaVersion
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'schemaVersion :: Maybe ByteString
_MessageMetadata'schemaVersion = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'schemaVersion" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'schemaVersion"
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'schemaVersion
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'schemaVersion :: Maybe ByteString
_MessageMetadata'schemaVersion = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "partitionKeyB64Encoded" Prelude.Bool where
fieldOf :: Proxy# "partitionKeyB64Encoded"
-> (Bool -> f Bool) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'partitionKeyB64Encoded
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_MessageMetadata'partitionKeyB64Encoded = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'partitionKeyB64Encoded" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'partitionKeyB64Encoded"
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'partitionKeyB64Encoded
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_MessageMetadata'partitionKeyB64Encoded = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "orderingKey" Data.ByteString.ByteString where
fieldOf :: Proxy# "orderingKey"
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'orderingKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'orderingKey :: Maybe ByteString
_MessageMetadata'orderingKey = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'orderingKey" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'orderingKey"
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe ByteString)
-> (MessageMetadata -> Maybe ByteString -> MessageMetadata)
-> Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe ByteString
_MessageMetadata'orderingKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe ByteString
y__ -> MessageMetadata
x__ {_MessageMetadata'orderingKey :: Maybe ByteString
_MessageMetadata'orderingKey = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "deliverAtTime" Data.Int.Int64 where
fieldOf :: Proxy# "deliverAtTime"
-> (Int64 -> f Int64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int64 -> f (Maybe Int64))
-> MessageMetadata -> f MessageMetadata)
-> ((Int64 -> f Int64) -> Maybe Int64 -> f (Maybe Int64))
-> (Int64 -> f Int64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int64)
-> (MessageMetadata -> Maybe Int64 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int64) (Maybe Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int64
_MessageMetadata'deliverAtTime
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int64
y__ -> MessageMetadata
x__ {_MessageMetadata'deliverAtTime :: Maybe Int64
_MessageMetadata'deliverAtTime = Maybe Int64
y__}))
(Int64 -> Lens' (Maybe Int64) Int64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'deliverAtTime" (Prelude.Maybe Data.Int.Int64) where
fieldOf :: Proxy# "maybe'deliverAtTime"
-> (Maybe Int64 -> f (Maybe Int64))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int64 -> f (Maybe Int64))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int64 -> f (Maybe Int64))
-> Maybe Int64 -> f (Maybe Int64))
-> (Maybe Int64 -> f (Maybe Int64))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int64)
-> (MessageMetadata -> Maybe Int64 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int64) (Maybe Int64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int64
_MessageMetadata'deliverAtTime
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int64
y__ -> MessageMetadata
x__ {_MessageMetadata'deliverAtTime :: Maybe Int64
_MessageMetadata'deliverAtTime = Maybe Int64
y__}))
(Maybe Int64 -> f (Maybe Int64)) -> Maybe Int64 -> f (Maybe Int64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "markerType" Data.Int.Int32 where
fieldOf :: Proxy# "markerType"
-> (Int32 -> f Int32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'markerType
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'markerType :: Maybe Int32
_MessageMetadata'markerType = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'markerType" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'markerType"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'markerType
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'markerType :: Maybe Int32
_MessageMetadata'markerType = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "txnidLeastBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidLeastBits"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidLeastBits
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'txnidLeastBits :: Maybe Word64
_MessageMetadata'txnidLeastBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'txnidLeastBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidLeastBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidLeastBits
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'txnidLeastBits :: Maybe Word64
_MessageMetadata'txnidLeastBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "txnidMostBits" Data.Word.Word64 where
fieldOf :: Proxy# "txnidMostBits"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidMostBits
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'txnidMostBits :: Maybe Word64
_MessageMetadata'txnidMostBits = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'txnidMostBits" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'txnidMostBits"
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'txnidMostBits
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'txnidMostBits :: Maybe Word64
_MessageMetadata'txnidMostBits = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "highestSequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "highestSequenceId"
-> (Word64 -> f Word64) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'highestSequenceId
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'highestSequenceId :: Maybe Word64
_MessageMetadata'highestSequenceId = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'highestSequenceId" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'highestSequenceId"
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Word64)
-> (MessageMetadata -> Maybe Word64 -> MessageMetadata)
-> Lens
MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Word64
_MessageMetadata'highestSequenceId
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Word64
y__ -> MessageMetadata
x__ {_MessageMetadata'highestSequenceId :: Maybe Word64
_MessageMetadata'highestSequenceId = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "nullValue" Prelude.Bool where
fieldOf :: Proxy# "nullValue"
-> (Bool -> f Bool) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'nullValue
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'nullValue :: Maybe Bool
_MessageMetadata'nullValue = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'nullValue" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'nullValue"
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'nullValue
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'nullValue :: Maybe Bool
_MessageMetadata'nullValue = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "uuid" Data.Text.Text where
fieldOf :: Proxy# "uuid"
-> (Text -> f Text) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'uuid
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'uuid :: Maybe Text
_MessageMetadata'uuid = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'uuid" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'uuid"
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Text)
-> (MessageMetadata -> Maybe Text -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Text
_MessageMetadata'uuid
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Text
y__ -> MessageMetadata
x__ {_MessageMetadata'uuid :: Maybe Text
_MessageMetadata'uuid = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "numChunksFromMsg" Data.Int.Int32 where
fieldOf :: Proxy# "numChunksFromMsg"
-> (Int32 -> f Int32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'numChunksFromMsg
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'numChunksFromMsg :: Maybe Int32
_MessageMetadata'numChunksFromMsg = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'numChunksFromMsg" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'numChunksFromMsg"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'numChunksFromMsg
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'numChunksFromMsg :: Maybe Int32
_MessageMetadata'numChunksFromMsg = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "totalChunkMsgSize" Data.Int.Int32 where
fieldOf :: Proxy# "totalChunkMsgSize"
-> (Int32 -> f Int32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'totalChunkMsgSize
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'totalChunkMsgSize :: Maybe Int32
_MessageMetadata'totalChunkMsgSize = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'totalChunkMsgSize" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'totalChunkMsgSize"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'totalChunkMsgSize
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'totalChunkMsgSize :: Maybe Int32
_MessageMetadata'totalChunkMsgSize = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "chunkId" Data.Int.Int32 where
fieldOf :: Proxy# "chunkId"
-> (Int32 -> f Int32) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Int32 -> f Int32) -> Maybe Int32 -> f (Maybe Int32))
-> (Int32 -> f Int32)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'chunkId
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'chunkId :: Maybe Int32
_MessageMetadata'chunkId = Maybe Int32
y__}))
(Int32 -> Lens' (Maybe Int32) Int32
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'chunkId" (Prelude.Maybe Data.Int.Int32) where
fieldOf :: Proxy# "maybe'chunkId"
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Int32 -> f (Maybe Int32))
-> Maybe Int32 -> f (Maybe Int32))
-> (Maybe Int32 -> f (Maybe Int32))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Int32)
-> (MessageMetadata -> Maybe Int32 -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Int32
_MessageMetadata'chunkId
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Int32
y__ -> MessageMetadata
x__ {_MessageMetadata'chunkId :: Maybe Int32
_MessageMetadata'chunkId = Maybe Int32
y__}))
(Maybe Int32 -> f (Maybe Int32)) -> Maybe Int32 -> f (Maybe Int32)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField MessageMetadata "nullPartitionKey" Prelude.Bool where
fieldOf :: Proxy# "nullPartitionKey"
-> (Bool -> f Bool) -> MessageMetadata -> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'nullPartitionKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'nullPartitionKey :: Maybe Bool
_MessageMetadata'nullPartitionKey = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField MessageMetadata "maybe'nullPartitionKey" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'nullPartitionKey"
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> MessageMetadata -> f MessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> MessageMetadata
-> f MessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((MessageMetadata -> Maybe Bool)
-> (MessageMetadata -> Maybe Bool -> MessageMetadata)
-> Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> Maybe Bool
_MessageMetadata'nullPartitionKey
(\ x__ :: MessageMetadata
x__ y__ :: Maybe Bool
y__ -> MessageMetadata
x__ {_MessageMetadata'nullPartitionKey :: Maybe Bool
_MessageMetadata'nullPartitionKey = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message MessageMetadata where
messageName :: Proxy MessageMetadata -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.MessageMetadata"
packedMessageDescriptor :: Proxy MessageMetadata -> ByteString
packedMessageDescriptor _
= "\n\
\\SIMessageMetadata\DC2#\n\
\\rproducer_name\CAN\SOH \STX(\tR\fproducerName\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2!\n\
\\fpublish_time\CAN\ETX \STX(\EOTR\vpublishTime\DC26\n\
\\n\
\properties\CAN\EOT \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\DC2'\n\
\\SIreplicated_from\CAN\ENQ \SOH(\tR\SOreplicatedFrom\DC2#\n\
\\rpartition_key\CAN\ACK \SOH(\tR\fpartitionKey\DC2!\n\
\\freplicate_to\CAN\a \ETX(\tR\vreplicateTo\DC2E\n\
\\vcompression\CAN\b \SOH(\SO2\GS.pulsar.proto.CompressionType:\EOTNONER\vcompression\DC2.\n\
\\DC1uncompressed_size\CAN\t \SOH(\r:\SOH0R\DLEuncompressedSize\DC24\n\
\\NAKnum_messages_in_batch\CAN\v \SOH(\ENQ:\SOH1R\DC2numMessagesInBatch\DC2 \n\
\\n\
\event_time\CAN\f \SOH(\EOT:\SOH0R\teventTime\DC2E\n\
\\SIencryption_keys\CAN\r \ETX(\v2\FS.pulsar.proto.EncryptionKeysR\SOencryptionKeys\DC2'\n\
\\SIencryption_algo\CAN\SO \SOH(\tR\SOencryptionAlgo\DC2)\n\
\\DLEencryption_param\CAN\SI \SOH(\fR\SIencryptionParam\DC2%\n\
\\SOschema_version\CAN\DLE \SOH(\fR\rschemaVersion\DC2@\n\
\\EMpartition_key_b64_encoded\CAN\DC1 \SOH(\b:\ENQfalseR\SYNpartitionKeyB64Encoded\DC2!\n\
\\fordering_key\CAN\DC2 \SOH(\fR\vorderingKey\DC2&\n\
\\SIdeliver_at_time\CAN\DC3 \SOH(\ETXR\rdeliverAtTime\DC2\US\n\
\\vmarker_type\CAN\DC4 \SOH(\ENQR\n\
\markerType\DC2(\n\
\\DLEtxnid_least_bits\CAN\SYN \SOH(\EOTR\SOtxnidLeastBits\DC2&\n\
\\SItxnid_most_bits\CAN\ETB \SOH(\EOTR\rtxnidMostBits\DC21\n\
\\DC3highest_sequence_id\CAN\CAN \SOH(\EOT:\SOH0R\DC1highestSequenceId\DC2$\n\
\\n\
\null_value\CAN\EM \SOH(\b:\ENQfalseR\tnullValue\DC2\DC2\n\
\\EOTuuid\CAN\SUB \SOH(\tR\EOTuuid\DC2-\n\
\\DC3num_chunks_from_msg\CAN\ESC \SOH(\ENQR\DLEnumChunksFromMsg\DC2/\n\
\\DC4total_chunk_msg_size\CAN\FS \SOH(\ENQR\DC1totalChunkMsgSize\DC2\EM\n\
\\bchunk_id\CAN\GS \SOH(\ENQR\achunkId\DC23\n\
\\DC2null_partition_key\CAN\RS \SOH(\b:\ENQfalseR\DLEnullPartitionKey"
packedFileDescriptor :: Proxy MessageMetadata -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor MessageMetadata)
fieldsByTag
= let
producerName__field_descriptor :: FieldDescriptor MessageMetadata
producerName__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"producer_name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens MessageMetadata MessageMetadata Text Text
-> FieldAccessor MessageMetadata Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
sequenceId__field_descriptor :: FieldDescriptor MessageMetadata
sequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens MessageMetadata MessageMetadata Word64 Word64
-> FieldAccessor MessageMetadata Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
publishTime__field_descriptor :: FieldDescriptor MessageMetadata
publishTime__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"publish_time"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(WireDefault Word64
-> Lens MessageMetadata MessageMetadata Word64 Word64
-> FieldAccessor MessageMetadata Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "publishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"publishTime")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
properties__field_descriptor :: FieldDescriptor MessageMetadata
properties__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor MessageMetadata KeyValue
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"properties"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing
-> Lens' MessageMetadata [KeyValue]
-> FieldAccessor MessageMetadata KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"properties")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
replicatedFrom__field_descriptor :: FieldDescriptor MessageMetadata
replicatedFrom__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"replicated_from"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
-> FieldAccessor MessageMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'replicatedFrom" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'replicatedFrom")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
partitionKey__field_descriptor :: FieldDescriptor MessageMetadata
partitionKey__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partition_key"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
-> FieldAccessor MessageMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKey")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
replicateTo__field_descriptor :: FieldDescriptor MessageMetadata
replicateTo__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"replicate_to"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Packing
-> Lens' MessageMetadata [Text]
-> FieldAccessor MessageMetadata Text
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "replicateTo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"replicateTo")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
compression__field_descriptor :: FieldDescriptor MessageMetadata
compression__field_descriptor
= String
-> FieldTypeDescriptor CompressionType
-> FieldAccessor MessageMetadata CompressionType
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"compression"
(ScalarField CompressionType -> FieldTypeDescriptor CompressionType
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField CompressionType
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor CompressionType)
(Lens
MessageMetadata
MessageMetadata
(Maybe CompressionType)
(Maybe CompressionType)
-> FieldAccessor MessageMetadata CompressionType
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'compression" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'compression")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
uncompressedSize__field_descriptor :: FieldDescriptor MessageMetadata
uncompressedSize__field_descriptor
= String
-> FieldTypeDescriptor Word32
-> FieldAccessor MessageMetadata Word32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"uncompressed_size"
(ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
(Lens MessageMetadata MessageMetadata (Maybe Word32) (Maybe Word32)
-> FieldAccessor MessageMetadata Word32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'uncompressedSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'uncompressedSize")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
numMessagesInBatch__field_descriptor :: FieldDescriptor MessageMetadata
numMessagesInBatch__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageMetadata Int32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"num_messages_in_batch"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageMetadata Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'numMessagesInBatch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'numMessagesInBatch")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
eventTime__field_descriptor :: FieldDescriptor MessageMetadata
eventTime__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"event_time"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
-> FieldAccessor MessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'eventTime")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
encryptionKeys__field_descriptor :: FieldDescriptor MessageMetadata
encryptionKeys__field_descriptor
= String
-> FieldTypeDescriptor EncryptionKeys
-> FieldAccessor MessageMetadata EncryptionKeys
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"encryption_keys"
(MessageOrGroup -> FieldTypeDescriptor EncryptionKeys
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor EncryptionKeys)
(Packing
-> Lens' MessageMetadata [EncryptionKeys]
-> FieldAccessor MessageMetadata EncryptionKeys
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "encryptionKeys" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"encryptionKeys")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
encryptionAlgo__field_descriptor :: FieldDescriptor MessageMetadata
encryptionAlgo__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"encryption_algo"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
-> FieldAccessor MessageMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'encryptionAlgo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'encryptionAlgo")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
encryptionParam__field_descriptor :: FieldDescriptor MessageMetadata
encryptionParam__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor MessageMetadata ByteString
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"encryption_param"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor MessageMetadata ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'encryptionParam" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'encryptionParam")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
schemaVersion__field_descriptor :: FieldDescriptor MessageMetadata
schemaVersion__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor MessageMetadata ByteString
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_version"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor MessageMetadata ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'schemaVersion")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
partitionKeyB64Encoded__field_descriptor :: FieldDescriptor MessageMetadata
partitionKeyB64Encoded__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor MessageMetadata Bool
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partition_key_b64_encoded"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
-> FieldAccessor MessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKeyB64Encoded")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
orderingKey__field_descriptor :: FieldDescriptor MessageMetadata
orderingKey__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor MessageMetadata ByteString
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ordering_key"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor MessageMetadata ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'orderingKey")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
deliverAtTime__field_descriptor :: FieldDescriptor MessageMetadata
deliverAtTime__field_descriptor
= String
-> FieldTypeDescriptor Int64
-> FieldAccessor MessageMetadata Int64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"deliver_at_time"
(ScalarField Int64 -> FieldTypeDescriptor Int64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int64
Data.ProtoLens.Int64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int64)
(Lens MessageMetadata MessageMetadata (Maybe Int64) (Maybe Int64)
-> FieldAccessor MessageMetadata Int64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'deliverAtTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'deliverAtTime")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
markerType__field_descriptor :: FieldDescriptor MessageMetadata
markerType__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageMetadata Int32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"marker_type"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageMetadata Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'markerType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'markerType")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
txnidLeastBits__field_descriptor :: FieldDescriptor MessageMetadata
txnidLeastBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_least_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
-> FieldAccessor MessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidLeastBits")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
txnidMostBits__field_descriptor :: FieldDescriptor MessageMetadata
txnidMostBits__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"txnid_most_bits"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
-> FieldAccessor MessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'txnidMostBits")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
highestSequenceId__field_descriptor :: FieldDescriptor MessageMetadata
highestSequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor MessageMetadata Word64
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"highest_sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens MessageMetadata MessageMetadata (Maybe Word64) (Maybe Word64)
-> FieldAccessor MessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'highestSequenceId")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
nullValue__field_descriptor :: FieldDescriptor MessageMetadata
nullValue__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor MessageMetadata Bool
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"null_value"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
-> FieldAccessor MessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nullValue")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
uuid__field_descriptor :: FieldDescriptor MessageMetadata
uuid__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor MessageMetadata Text
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"uuid"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens MessageMetadata MessageMetadata (Maybe Text) (Maybe Text)
-> FieldAccessor MessageMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'uuid" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'uuid")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
numChunksFromMsg__field_descriptor :: FieldDescriptor MessageMetadata
numChunksFromMsg__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageMetadata Int32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"num_chunks_from_msg"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageMetadata Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'numChunksFromMsg" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'numChunksFromMsg")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
totalChunkMsgSize__field_descriptor :: FieldDescriptor MessageMetadata
totalChunkMsgSize__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageMetadata Int32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"total_chunk_msg_size"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageMetadata Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'totalChunkMsgSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'totalChunkMsgSize")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
chunkId__field_descriptor :: FieldDescriptor MessageMetadata
chunkId__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor MessageMetadata Int32
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"chunk_id"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(Lens MessageMetadata MessageMetadata (Maybe Int32) (Maybe Int32)
-> FieldAccessor MessageMetadata Int32
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'chunkId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'chunkId")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
nullPartitionKey__field_descriptor :: FieldDescriptor MessageMetadata
nullPartitionKey__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor MessageMetadata Bool
-> FieldDescriptor MessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"null_partition_key"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens MessageMetadata MessageMetadata (Maybe Bool) (Maybe Bool)
-> FieldAccessor MessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nullPartitionKey")) ::
Data.ProtoLens.FieldDescriptor MessageMetadata
in
[(Tag, FieldDescriptor MessageMetadata)]
-> Map Tag (FieldDescriptor MessageMetadata)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor MessageMetadata
producerName__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor MessageMetadata
sequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor MessageMetadata
publishTime__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor MessageMetadata
properties__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor MessageMetadata
replicatedFrom__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor MessageMetadata
partitionKey__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor MessageMetadata
replicateTo__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor MessageMetadata
compression__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor MessageMetadata
uncompressedSize__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 11, FieldDescriptor MessageMetadata
numMessagesInBatch__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 12, FieldDescriptor MessageMetadata
eventTime__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 13, FieldDescriptor MessageMetadata
encryptionKeys__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 14, FieldDescriptor MessageMetadata
encryptionAlgo__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 15, FieldDescriptor MessageMetadata
encryptionParam__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 16, FieldDescriptor MessageMetadata
schemaVersion__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 17, FieldDescriptor MessageMetadata
partitionKeyB64Encoded__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 18, FieldDescriptor MessageMetadata
orderingKey__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 19, FieldDescriptor MessageMetadata
deliverAtTime__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 20, FieldDescriptor MessageMetadata
markerType__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 22, FieldDescriptor MessageMetadata
txnidLeastBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 23, FieldDescriptor MessageMetadata
txnidMostBits__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 24, FieldDescriptor MessageMetadata
highestSequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 25, FieldDescriptor MessageMetadata
nullValue__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 26, FieldDescriptor MessageMetadata
uuid__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 27, FieldDescriptor MessageMetadata
numChunksFromMsg__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 28, FieldDescriptor MessageMetadata
totalChunkMsgSize__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 29, FieldDescriptor MessageMetadata
chunkId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 30, FieldDescriptor MessageMetadata
nullPartitionKey__field_descriptor)]
unknownFields :: LensLike' f MessageMetadata FieldSet
unknownFields
= (MessageMetadata -> FieldSet)
-> (MessageMetadata -> FieldSet -> MessageMetadata)
-> Lens' MessageMetadata FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
MessageMetadata -> FieldSet
_MessageMetadata'_unknownFields
(\ x__ :: MessageMetadata
x__ y__ :: FieldSet
y__ -> MessageMetadata
x__ {_MessageMetadata'_unknownFields :: FieldSet
_MessageMetadata'_unknownFields = FieldSet
y__})
defMessage :: MessageMetadata
defMessage
= $WMessageMetadata'_constructor :: Text
-> Word64
-> Word64
-> Vector KeyValue
-> Maybe Text
-> Maybe Text
-> Vector Text
-> Maybe CompressionType
-> Maybe Word32
-> Maybe Int32
-> Maybe Word64
-> Vector EncryptionKeys
-> Maybe Text
-> Maybe ByteString
-> Maybe ByteString
-> Maybe Bool
-> Maybe ByteString
-> Maybe Int64
-> Maybe Int32
-> Maybe Word64
-> Maybe Word64
-> Maybe Word64
-> Maybe Bool
-> Maybe Text
-> Maybe Int32
-> Maybe Int32
-> Maybe Int32
-> Maybe Bool
-> FieldSet
-> MessageMetadata
MessageMetadata'_constructor
{_MessageMetadata'producerName :: Text
_MessageMetadata'producerName = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_MessageMetadata'sequenceId :: Word64
_MessageMetadata'sequenceId = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_MessageMetadata'publishTime :: Word64
_MessageMetadata'publishTime = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_MessageMetadata'properties :: Vector KeyValue
_MessageMetadata'properties = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_MessageMetadata'replicatedFrom :: Maybe Text
_MessageMetadata'replicatedFrom = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'partitionKey :: Maybe Text
_MessageMetadata'partitionKey = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'replicateTo :: Vector Text
_MessageMetadata'replicateTo = Vector Text
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_MessageMetadata'compression :: Maybe CompressionType
_MessageMetadata'compression = Maybe CompressionType
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'uncompressedSize :: Maybe Word32
_MessageMetadata'uncompressedSize = Maybe Word32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'numMessagesInBatch :: Maybe Int32
_MessageMetadata'numMessagesInBatch = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'eventTime :: Maybe Word64
_MessageMetadata'eventTime = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'encryptionKeys :: Vector EncryptionKeys
_MessageMetadata'encryptionKeys = Vector EncryptionKeys
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_MessageMetadata'encryptionAlgo :: Maybe Text
_MessageMetadata'encryptionAlgo = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'encryptionParam :: Maybe ByteString
_MessageMetadata'encryptionParam = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'schemaVersion :: Maybe ByteString
_MessageMetadata'schemaVersion = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_MessageMetadata'partitionKeyB64Encoded = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'orderingKey :: Maybe ByteString
_MessageMetadata'orderingKey = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'deliverAtTime :: Maybe Int64
_MessageMetadata'deliverAtTime = Maybe Int64
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'markerType :: Maybe Int32
_MessageMetadata'markerType = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'txnidLeastBits :: Maybe Word64
_MessageMetadata'txnidLeastBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'txnidMostBits :: Maybe Word64
_MessageMetadata'txnidMostBits = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'highestSequenceId :: Maybe Word64
_MessageMetadata'highestSequenceId = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'nullValue :: Maybe Bool
_MessageMetadata'nullValue = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'uuid :: Maybe Text
_MessageMetadata'uuid = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'numChunksFromMsg :: Maybe Int32
_MessageMetadata'numChunksFromMsg = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'totalChunkMsgSize :: Maybe Int32
_MessageMetadata'totalChunkMsgSize = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'chunkId :: Maybe Int32
_MessageMetadata'chunkId = Maybe Int32
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'nullPartitionKey :: Maybe Bool
_MessageMetadata'nullPartitionKey = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_MessageMetadata'_unknownFields :: FieldSet
_MessageMetadata'_unknownFields = []}
parseMessage :: Parser MessageMetadata
parseMessage
= let
loop ::
MessageMetadata
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld EncryptionKeys
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Data.Text.Text
-> Data.ProtoLens.Encoding.Bytes.Parser MessageMetadata
loop :: MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
x :: MessageMetadata
x
required'producerName :: Bool
required'producerName
required'publishTime :: Bool
required'publishTime
required'sequenceId :: Bool
required'sequenceId
mutable'encryptionKeys :: Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
mutable'properties :: Growing Vector RealWorld KeyValue
mutable'properties
mutable'replicateTo :: Growing Vector RealWorld Text
mutable'replicateTo
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector EncryptionKeys
frozen'encryptionKeys <- IO (Vector EncryptionKeys) -> Parser (Vector EncryptionKeys)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) EncryptionKeys
-> IO (Vector EncryptionKeys)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld EncryptionKeys
Growing Vector (PrimState IO) EncryptionKeys
mutable'encryptionKeys)
Vector KeyValue
frozen'properties <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties)
Vector Text
frozen'replicateTo <- IO (Vector Text) -> Parser (Vector Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text -> IO (Vector Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'replicateTo)
(let
missing :: [String]
missing
= (if Bool
required'producerName then
(:) "producer_name"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'publishTime then (:) "publish_time" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'sequenceId then (:) "sequence_id" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
MessageMetadata -> Parser MessageMetadata
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter MessageMetadata MessageMetadata FieldSet FieldSet
-> (FieldSet -> FieldSet) -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter MessageMetadata MessageMetadata FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
MessageMetadata
MessageMetadata
(Vector EncryptionKeys)
(Vector EncryptionKeys)
-> Vector EncryptionKeys -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'encryptionKeys" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'encryptionKeys")
Vector EncryptionKeys
frozen'encryptionKeys
(Setter
MessageMetadata MessageMetadata (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties")
Vector KeyValue
frozen'properties
(Setter MessageMetadata MessageMetadata (Vector Text) (Vector Text)
-> Vector Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'replicateTo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'replicateTo")
Vector Text
frozen'replicateTo
MessageMetadata
x))))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"producer_name"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Text Text
-> Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName") Text
y MessageMetadata
x)
Bool
Prelude.False
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
16
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "sequence_id"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
Prelude.False
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
24
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "publish_time"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "publishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"publishTime") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
Prelude.False
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
34
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"properties"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties KeyValue
y)
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
MessageMetadata
x
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
v
Growing Vector RealWorld Text
mutable'replicateTo
42
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"replicated_from"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Text Text
-> Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "replicatedFrom" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"replicatedFrom") Text
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
50
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"partition_key"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Text Text
-> Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionKey") Text
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
58
-> do !Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"replicate_to"
Growing Vector RealWorld Text
v <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) Text
-> Text -> IO (Growing Vector (PrimState IO) Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
Growing Vector RealWorld Text
Growing Vector (PrimState IO) Text
mutable'replicateTo Text
y)
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
MessageMetadata
x
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
v
64
-> do CompressionType
y <- Parser CompressionType -> String -> Parser CompressionType
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> CompressionType) -> Parser Int -> Parser CompressionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> CompressionType
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"compression"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter
MessageMetadata MessageMetadata CompressionType CompressionType
-> CompressionType -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "compression" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"compression") CompressionType
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
72
-> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"uncompressed_size"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word32 Word32
-> Word32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "uncompressedSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"uncompressedSize") Word32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
88
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"num_messages_in_batch"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int32 Int32
-> Int32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "numMessagesInBatch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"numMessagesInBatch") Int32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
96
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "event_time"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"eventTime") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
106
-> do !EncryptionKeys
y <- Parser EncryptionKeys -> String -> Parser EncryptionKeys
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser EncryptionKeys -> Parser EncryptionKeys
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser EncryptionKeys
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"encryption_keys"
Growing Vector RealWorld EncryptionKeys
v <- IO (Growing Vector RealWorld EncryptionKeys)
-> Parser (Growing Vector RealWorld EncryptionKeys)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) EncryptionKeys
-> EncryptionKeys
-> IO (Growing Vector (PrimState IO) EncryptionKeys)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
Growing Vector RealWorld EncryptionKeys
Growing Vector (PrimState IO) EncryptionKeys
mutable'encryptionKeys EncryptionKeys
y)
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
MessageMetadata
x
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
v
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
114
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"encryption_algo"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Text Text
-> Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "encryptionAlgo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"encryptionAlgo") Text
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
122
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"encryption_param"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata ByteString ByteString
-> ByteString -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "encryptionParam" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"encryptionParam") ByteString
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
130
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_version"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata ByteString ByteString
-> ByteString -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaVersion") ByteString
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
136
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"partition_key_b64_encoded"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Bool Bool
-> Bool -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionKeyB64Encoded") Bool
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
146
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"ordering_key"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata ByteString ByteString
-> ByteString -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"orderingKey") ByteString
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
152
-> do Int64
y <- Parser Int64 -> String -> Parser Int64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int64) -> Parser Word64 -> Parser Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"deliver_at_time"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int64 Int64
-> Int64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "deliverAtTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"deliverAtTime") Int64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
160
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"marker_type"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int32 Int32
-> Int32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "markerType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"markerType") Int32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
176
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_least_bits"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidLeastBits") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
184
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "txnid_most_bits"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"txnidMostBits") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
192
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "highest_sequence_id"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Word64 Word64
-> Word64 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"highestSequenceId") Word64
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
200
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"null_value"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Bool Bool
-> Bool -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nullValue") Bool
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
210
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"uuid"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Text Text
-> Text -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "uuid" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"uuid") Text
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
216
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"num_chunks_from_msg"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int32 Int32
-> Int32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "numChunksFromMsg" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"numChunksFromMsg") Int32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
224
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"total_chunk_msg_size"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int32 Int32
-> Int32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "totalChunkMsgSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"totalChunkMsgSize") Int32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
232
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"chunk_id"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Int32 Int32
-> Int32 -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "chunkId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"chunkId") Int32
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
240
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"null_partition_key"
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata Bool Bool
-> Bool -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nullPartitionKey") Bool
y MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
(Setter MessageMetadata MessageMetadata FieldSet FieldSet
-> (FieldSet -> FieldSet) -> MessageMetadata -> MessageMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter MessageMetadata MessageMetadata FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) MessageMetadata
x)
Bool
required'producerName
Bool
required'publishTime
Bool
required'sequenceId
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo
in
Parser MessageMetadata -> String -> Parser MessageMetadata
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys <- IO (Growing Vector RealWorld EncryptionKeys)
-> Parser (Growing Vector RealWorld EncryptionKeys)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld EncryptionKeys)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
Growing Vector RealWorld KeyValue
mutable'properties <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
Growing Vector RealWorld Text
mutable'replicateTo <- IO (Growing Vector RealWorld Text)
-> Parser (Growing Vector RealWorld Text)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld Text)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
MessageMetadata
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld EncryptionKeys
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Text
-> Parser MessageMetadata
loop
MessageMetadata
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld EncryptionKeys
mutable'encryptionKeys
Growing Vector RealWorld KeyValue
mutable'properties
Growing Vector RealWorld Text
mutable'replicateTo)
"MessageMetadata"
buildMessage :: MessageMetadata -> Builder
buildMessage
= \ _x :: MessageMetadata
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text MessageMetadata MessageMetadata Text Text
-> MessageMetadata -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "producerName" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"producerName") MessageMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 16)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 MessageMetadata MessageMetadata Word64 Word64
-> MessageMetadata -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") MessageMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(FoldLike Word64 MessageMetadata MessageMetadata Word64 Word64
-> MessageMetadata -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "publishTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"publishTime") MessageMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 34)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue)
MessageMetadata
MessageMetadata
(Vector KeyValue)
(Vector KeyValue)
-> MessageMetadata -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties") MessageMetadata
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
MessageMetadata
MessageMetadata
(Maybe Text)
(Maybe Text)
-> MessageMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'replicatedFrom" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'replicatedFrom") MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
MessageMetadata
MessageMetadata
(Maybe Text)
(Maybe Text)
-> MessageMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKey") MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 50)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((Text -> Builder) -> Vector Text -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: Text
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(FoldLike
(Vector Text)
MessageMetadata
MessageMetadata
(Vector Text)
(Vector Text)
-> MessageMetadata -> Vector Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'replicateTo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'replicateTo") MessageMetadata
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe CompressionType)
MessageMetadata
MessageMetadata
(Maybe CompressionType)
(Maybe CompressionType)
-> MessageMetadata -> Maybe CompressionType
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'compression" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'compression") MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: CompressionType
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
((Int -> Builder)
-> (CompressionType -> Int) -> CompressionType -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
CompressionType -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
CompressionType
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word32)
MessageMetadata
MessageMetadata
(Maybe Word32)
(Maybe Word32)
-> MessageMetadata -> Maybe Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'uncompressedSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'uncompressedSize")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 72)
((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Word32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageMetadata
MessageMetadata
(Maybe Int32)
(Maybe Int32)
-> MessageMetadata -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'numMessagesInBatch" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'numMessagesInBatch")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 88)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
MessageMetadata
MessageMetadata
(Maybe Word64)
(Maybe Word64)
-> MessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'eventTime") MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 96)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((EncryptionKeys -> Builder) -> Vector EncryptionKeys -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: EncryptionKeys
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
106)
((ByteString -> Builder)
-> (EncryptionKeys -> ByteString) -> EncryptionKeys -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
EncryptionKeys -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
EncryptionKeys
_v))
(FoldLike
(Vector EncryptionKeys)
MessageMetadata
MessageMetadata
(Vector EncryptionKeys)
(Vector EncryptionKeys)
-> MessageMetadata -> Vector EncryptionKeys
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'encryptionKeys" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"vec'encryptionKeys")
MessageMetadata
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
MessageMetadata
MessageMetadata
(Maybe Text)
(Maybe Text)
-> MessageMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'encryptionAlgo" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'encryptionAlgo")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
114)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> MessageMetadata -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'encryptionParam" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'encryptionParam")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
122)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
ByteString
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> MessageMetadata -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'schemaVersion" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'schemaVersion")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
130)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
ByteString
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
MessageMetadata
MessageMetadata
(Maybe Bool)
(Maybe Bool)
-> MessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'partitionKeyB64Encoded")
MessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
136)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
MessageMetadata
MessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> MessageMetadata -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'orderingKey")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
146)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
ByteString
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int64)
MessageMetadata
MessageMetadata
(Maybe Int64)
(Maybe Int64)
-> MessageMetadata -> Maybe Int64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'deliverAtTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'deliverAtTime")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
152)
((Word64 -> Builder) -> (Int64 -> Word64) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageMetadata
MessageMetadata
(Maybe Int32)
(Maybe Int32)
-> MessageMetadata -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'markerType" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'markerType")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
160)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
MessageMetadata
MessageMetadata
(Maybe Word64)
(Maybe Word64)
-> MessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidLeastBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'txnidLeastBits")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
176)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
MessageMetadata
MessageMetadata
(Maybe Word64)
(Maybe Word64)
-> MessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'txnidMostBits" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'txnidMostBits")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
184)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
MessageMetadata
MessageMetadata
(Maybe Word64)
(Maybe Word64)
-> MessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'highestSequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'highestSequenceId")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
192)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
MessageMetadata
MessageMetadata
(Maybe Bool)
(Maybe Bool)
-> MessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'nullValue")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
200)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b
-> if Bool
b then
1
else
0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
MessageMetadata
MessageMetadata
(Maybe Text)
(Maybe Text)
-> MessageMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'uuid" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'uuid")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
210)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length
ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageMetadata
MessageMetadata
(Maybe Int32)
(Maybe Int32)
-> MessageMetadata -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'numChunksFromMsg" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'numChunksFromMsg")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
216)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageMetadata
MessageMetadata
(Maybe Int32)
(Maybe Int32)
-> MessageMetadata -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'totalChunkMsgSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'totalChunkMsgSize")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
224)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Int32)
MessageMetadata
MessageMetadata
(Maybe Int32)
(Maybe Int32)
-> MessageMetadata -> Maybe Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'chunkId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'chunkId")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Int32
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
232)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Int32
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
MessageMetadata
MessageMetadata
(Maybe Bool)
(Maybe Bool)
-> MessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'nullPartitionKey")
MessageMetadata
_x
of
Prelude.Nothing
-> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
240)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b
-> if Bool
b then
1
else
0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet MessageMetadata MessageMetadata FieldSet FieldSet
-> MessageMetadata -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike FieldSet MessageMetadata MessageMetadata FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields
MessageMetadata
_x)))))))))))))))))))))))))))))
instance Control.DeepSeq.NFData MessageMetadata where
rnf :: MessageMetadata -> ()
rnf
= \ x__ :: MessageMetadata
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> FieldSet
_MessageMetadata'_unknownFields MessageMetadata
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Text
_MessageMetadata'producerName MessageMetadata
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Word64
_MessageMetadata'sequenceId MessageMetadata
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Word64
_MessageMetadata'publishTime MessageMetadata
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Vector KeyValue
_MessageMetadata'properties MessageMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Text
_MessageMetadata'replicatedFrom MessageMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Text
_MessageMetadata'partitionKey MessageMetadata
x__)
(Vector Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Vector Text
_MessageMetadata'replicateTo MessageMetadata
x__)
(Maybe CompressionType -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe CompressionType
_MessageMetadata'compression MessageMetadata
x__)
(Maybe Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Word32
_MessageMetadata'uncompressedSize MessageMetadata
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int32
_MessageMetadata'numMessagesInBatch MessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Word64
_MessageMetadata'eventTime MessageMetadata
x__)
(Vector EncryptionKeys -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Vector EncryptionKeys
_MessageMetadata'encryptionKeys MessageMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Text
_MessageMetadata'encryptionAlgo MessageMetadata
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe ByteString
_MessageMetadata'encryptionParam MessageMetadata
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe ByteString
_MessageMetadata'schemaVersion MessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Bool
_MessageMetadata'partitionKeyB64Encoded
MessageMetadata
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe ByteString
_MessageMetadata'orderingKey MessageMetadata
x__)
(Maybe Int64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int64
_MessageMetadata'deliverAtTime
MessageMetadata
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int32
_MessageMetadata'markerType
MessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Word64
_MessageMetadata'txnidLeastBits
MessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Word64
_MessageMetadata'txnidMostBits
MessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Word64
_MessageMetadata'highestSequenceId
MessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Bool
_MessageMetadata'nullValue
MessageMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Text
_MessageMetadata'uuid
MessageMetadata
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int32
_MessageMetadata'numChunksFromMsg
MessageMetadata
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int32
_MessageMetadata'totalChunkMsgSize
MessageMetadata
x__)
(Maybe Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Int32
_MessageMetadata'chunkId
MessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(MessageMetadata -> Maybe Bool
_MessageMetadata'nullPartitionKey
MessageMetadata
x__)
()))))))))))))))))))))))))))))
data ProtocolVersion
= V0 |
V1 |
V2 |
V3 |
V4 |
V5 |
V6 |
V7 |
V8 |
V9 |
V10 |
V11 |
V12 |
V13 |
V14 |
V15
deriving stock (Int -> ProtocolVersion -> ShowS
[ProtocolVersion] -> ShowS
ProtocolVersion -> String
(Int -> ProtocolVersion -> ShowS)
-> (ProtocolVersion -> String)
-> ([ProtocolVersion] -> ShowS)
-> Show ProtocolVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProtocolVersion] -> ShowS
$cshowList :: [ProtocolVersion] -> ShowS
show :: ProtocolVersion -> String
$cshow :: ProtocolVersion -> String
showsPrec :: Int -> ProtocolVersion -> ShowS
$cshowsPrec :: Int -> ProtocolVersion -> ShowS
Prelude.Show, ProtocolVersion -> ProtocolVersion -> Bool
(ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> Eq ProtocolVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProtocolVersion -> ProtocolVersion -> Bool
$c/= :: ProtocolVersion -> ProtocolVersion -> Bool
== :: ProtocolVersion -> ProtocolVersion -> Bool
$c== :: ProtocolVersion -> ProtocolVersion -> Bool
Prelude.Eq, Eq ProtocolVersion
Eq ProtocolVersion =>
(ProtocolVersion -> ProtocolVersion -> Ordering)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> ProtocolVersion)
-> (ProtocolVersion -> ProtocolVersion -> ProtocolVersion)
-> Ord ProtocolVersion
ProtocolVersion -> ProtocolVersion -> Bool
ProtocolVersion -> ProtocolVersion -> Ordering
ProtocolVersion -> ProtocolVersion -> ProtocolVersion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion
$cmin :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion
max :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion
$cmax :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion
>= :: ProtocolVersion -> ProtocolVersion -> Bool
$c>= :: ProtocolVersion -> ProtocolVersion -> Bool
> :: ProtocolVersion -> ProtocolVersion -> Bool
$c> :: ProtocolVersion -> ProtocolVersion -> Bool
<= :: ProtocolVersion -> ProtocolVersion -> Bool
$c<= :: ProtocolVersion -> ProtocolVersion -> Bool
< :: ProtocolVersion -> ProtocolVersion -> Bool
$c< :: ProtocolVersion -> ProtocolVersion -> Bool
compare :: ProtocolVersion -> ProtocolVersion -> Ordering
$ccompare :: ProtocolVersion -> ProtocolVersion -> Ordering
$cp1Ord :: Eq ProtocolVersion
Prelude.Ord)
instance Data.ProtoLens.MessageEnum ProtocolVersion where
maybeToEnum :: Int -> Maybe ProtocolVersion
maybeToEnum 0 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V0
maybeToEnum 1 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V1
maybeToEnum 2 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V2
maybeToEnum 3 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V3
maybeToEnum 4 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V4
maybeToEnum 5 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V5
maybeToEnum 6 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V6
maybeToEnum 7 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V7
maybeToEnum 8 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V8
maybeToEnum 9 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V9
maybeToEnum 10 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V10
maybeToEnum 11 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V11
maybeToEnum 12 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V12
maybeToEnum 13 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V13
maybeToEnum 14 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V14
maybeToEnum 15 = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V15
maybeToEnum _ = Maybe ProtocolVersion
forall a. Maybe a
Prelude.Nothing
showEnum :: ProtocolVersion -> String
showEnum V0 = "v0"
showEnum V1 = "v1"
showEnum V2 = "v2"
showEnum V3 = "v3"
showEnum V4 = "v4"
showEnum V5 = "v5"
showEnum V6 = "v6"
showEnum V7 = "v7"
showEnum V8 = "v8"
showEnum V9 = "v9"
showEnum V10 = "v10"
showEnum V11 = "v11"
showEnum V12 = "v12"
showEnum V13 = "v13"
showEnum V14 = "v14"
showEnum V15 = "v15"
readEnum :: String -> Maybe ProtocolVersion
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v0" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V0
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v1" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V1
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v2" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V2
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v3" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V3
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v4" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V4
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v5" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V5
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v6" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V6
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v7" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V7
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v8" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V8
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v9" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V9
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v10" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V10
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v11" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V11
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v12" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V12
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v13" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V13
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v14" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V14
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "v15" = ProtocolVersion -> Maybe ProtocolVersion
forall a. a -> Maybe a
Prelude.Just ProtocolVersion
V15
| Bool
Prelude.otherwise
= Maybe Int
-> (Int -> Maybe ProtocolVersion) -> Maybe ProtocolVersion
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe ProtocolVersion
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded ProtocolVersion where
minBound :: ProtocolVersion
minBound = ProtocolVersion
V0
maxBound :: ProtocolVersion
maxBound = ProtocolVersion
V15
instance Prelude.Enum ProtocolVersion where
toEnum :: Int -> ProtocolVersion
toEnum k__ :: Int
k__
= ProtocolVersion
-> (ProtocolVersion -> ProtocolVersion)
-> Maybe ProtocolVersion
-> ProtocolVersion
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> ProtocolVersion
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum ProtocolVersion: "
(Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
ProtocolVersion -> ProtocolVersion
forall a. a -> a
Prelude.id
(Int -> Maybe ProtocolVersion
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: ProtocolVersion -> Int
fromEnum V0 = 0
fromEnum V1 = 1
fromEnum V2 = 2
fromEnum V3 = 3
fromEnum V4 = 4
fromEnum V5 = 5
fromEnum V6 = 6
fromEnum V7 = 7
fromEnum V8 = 8
fromEnum V9 = 9
fromEnum V10 = 10
fromEnum V11 = 11
fromEnum V12 = 12
fromEnum V13 = 13
fromEnum V14 = 14
fromEnum V15 = 15
succ :: ProtocolVersion -> ProtocolVersion
succ V15
= String -> ProtocolVersion
forall a. HasCallStack => String -> a
Prelude.error
"ProtocolVersion.succ: bad argument V15. This value would be out of bounds."
succ V0 = ProtocolVersion
V1
succ V1 = ProtocolVersion
V2
succ V2 = ProtocolVersion
V3
succ V3 = ProtocolVersion
V4
succ V4 = ProtocolVersion
V5
succ V5 = ProtocolVersion
V6
succ V6 = ProtocolVersion
V7
succ V7 = ProtocolVersion
V8
succ V8 = ProtocolVersion
V9
succ V9 = ProtocolVersion
V10
succ V10 = ProtocolVersion
V11
succ V11 = ProtocolVersion
V12
succ V12 = ProtocolVersion
V13
succ V13 = ProtocolVersion
V14
succ V14 = ProtocolVersion
V15
pred :: ProtocolVersion -> ProtocolVersion
pred V0
= String -> ProtocolVersion
forall a. HasCallStack => String -> a
Prelude.error
"ProtocolVersion.pred: bad argument V0. This value would be out of bounds."
pred V1 = ProtocolVersion
V0
pred V2 = ProtocolVersion
V1
pred V3 = ProtocolVersion
V2
pred V4 = ProtocolVersion
V3
pred V5 = ProtocolVersion
V4
pred V6 = ProtocolVersion
V5
pred V7 = ProtocolVersion
V6
pred V8 = ProtocolVersion
V7
pred V9 = ProtocolVersion
V8
pred V10 = ProtocolVersion
V9
pred V11 = ProtocolVersion
V10
pred V12 = ProtocolVersion
V11
pred V13 = ProtocolVersion
V12
pred V14 = ProtocolVersion
V13
pred V15 = ProtocolVersion
V14
enumFrom :: ProtocolVersion -> [ProtocolVersion]
enumFrom = ProtocolVersion -> [ProtocolVersion]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
enumFromTo = ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
enumFromThen = ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: ProtocolVersion
-> ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
enumFromThenTo = ProtocolVersion
-> ProtocolVersion -> ProtocolVersion -> [ProtocolVersion]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault ProtocolVersion where
fieldDefault :: ProtocolVersion
fieldDefault = ProtocolVersion
V0
instance Control.DeepSeq.NFData ProtocolVersion where
rnf :: ProtocolVersion -> ()
rnf x__ :: ProtocolVersion
x__ = ProtocolVersion -> () -> ()
forall a b. a -> b -> b
Prelude.seq ProtocolVersion
x__ ()
data Schema
= Schema'_constructor {Schema -> Text
_Schema'name :: !Data.Text.Text,
Schema -> ByteString
_Schema'schemaData :: !Data.ByteString.ByteString,
Schema -> Schema'Type
_Schema'type' :: !Schema'Type,
Schema -> Vector KeyValue
_Schema'properties :: !(Data.Vector.Vector KeyValue),
Schema -> FieldSet
_Schema'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (Schema -> Schema -> Bool
(Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool) -> Eq Schema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Schema -> Schema -> Bool
$c/= :: Schema -> Schema -> Bool
== :: Schema -> Schema -> Bool
$c== :: Schema -> Schema -> Bool
Prelude.Eq, Eq Schema
Eq Schema =>
(Schema -> Schema -> Ordering)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Schema)
-> (Schema -> Schema -> Schema)
-> Ord Schema
Schema -> Schema -> Bool
Schema -> Schema -> Ordering
Schema -> Schema -> Schema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Schema -> Schema -> Schema
$cmin :: Schema -> Schema -> Schema
max :: Schema -> Schema -> Schema
$cmax :: Schema -> Schema -> Schema
>= :: Schema -> Schema -> Bool
$c>= :: Schema -> Schema -> Bool
> :: Schema -> Schema -> Bool
$c> :: Schema -> Schema -> Bool
<= :: Schema -> Schema -> Bool
$c<= :: Schema -> Schema -> Bool
< :: Schema -> Schema -> Bool
$c< :: Schema -> Schema -> Bool
compare :: Schema -> Schema -> Ordering
$ccompare :: Schema -> Schema -> Ordering
$cp1Ord :: Eq Schema
Prelude.Ord)
instance Prelude.Show Schema where
showsPrec :: Int -> Schema -> ShowS
showsPrec _ __x :: Schema
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(Schema -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Schema
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField Schema "name" Data.Text.Text where
fieldOf :: Proxy# "name" -> (Text -> f Text) -> Schema -> f Schema
fieldOf _
= ((Text -> f Text) -> Schema -> f Schema)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Schema
-> f Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Schema -> Text)
-> (Schema -> Text -> Schema) -> Lens Schema Schema Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> Text
_Schema'name (\ x__ :: Schema
x__ y__ :: Text
y__ -> Schema
x__ {_Schema'name :: Text
_Schema'name = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Schema "schemaData" Data.ByteString.ByteString where
fieldOf :: Proxy# "schemaData"
-> (ByteString -> f ByteString) -> Schema -> f Schema
fieldOf _
= ((ByteString -> f ByteString) -> Schema -> f Schema)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Schema
-> f Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Schema -> ByteString)
-> (Schema -> ByteString -> Schema)
-> Lens Schema Schema ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> ByteString
_Schema'schemaData (\ x__ :: Schema
x__ y__ :: ByteString
y__ -> Schema
x__ {_Schema'schemaData :: ByteString
_Schema'schemaData = ByteString
y__}))
(ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Schema "type'" Schema'Type where
fieldOf :: Proxy# "type'"
-> (Schema'Type -> f Schema'Type) -> Schema -> f Schema
fieldOf _
= ((Schema'Type -> f Schema'Type) -> Schema -> f Schema)
-> ((Schema'Type -> f Schema'Type) -> Schema'Type -> f Schema'Type)
-> (Schema'Type -> f Schema'Type)
-> Schema
-> f Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Schema -> Schema'Type)
-> (Schema -> Schema'Type -> Schema)
-> Lens Schema Schema Schema'Type Schema'Type
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> Schema'Type
_Schema'type' (\ x__ :: Schema
x__ y__ :: Schema'Type
y__ -> Schema
x__ {_Schema'type' :: Schema'Type
_Schema'type' = Schema'Type
y__}))
(Schema'Type -> f Schema'Type) -> Schema'Type -> f Schema'Type
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Schema "properties" [KeyValue] where
fieldOf :: Proxy# "properties"
-> ([KeyValue] -> f [KeyValue]) -> Schema -> f Schema
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue)) -> Schema -> f Schema)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> Schema
-> f Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Schema -> Vector KeyValue)
-> (Schema -> Vector KeyValue -> Schema)
-> Lens Schema Schema (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> Vector KeyValue
_Schema'properties (\ x__ :: Schema
x__ y__ :: Vector KeyValue
y__ -> Schema
x__ {_Schema'properties :: Vector KeyValue
_Schema'properties = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField Schema "vec'properties" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'properties"
-> (Vector KeyValue -> f (Vector KeyValue)) -> Schema -> f Schema
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue)) -> Schema -> f Schema)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> Schema
-> f Schema
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Schema -> Vector KeyValue)
-> (Schema -> Vector KeyValue -> Schema)
-> Lens Schema Schema (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> Vector KeyValue
_Schema'properties (\ x__ :: Schema
x__ y__ :: Vector KeyValue
y__ -> Schema
x__ {_Schema'properties :: Vector KeyValue
_Schema'properties = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Schema where
messageName :: Proxy Schema -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.Schema"
packedMessageDescriptor :: Proxy Schema -> ByteString
packedMessageDescriptor _
= "\n\
\\ACKSchema\DC2\DC2\n\
\\EOTname\CAN\SOH \STX(\tR\EOTname\DC2\US\n\
\\vschema_data\CAN\ETX \STX(\fR\n\
\schemaData\DC2-\n\
\\EOTtype\CAN\EOT \STX(\SO2\EM.pulsar.proto.Schema.TypeR\EOTtype\DC26\n\
\\n\
\properties\CAN\ENQ \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\"\187\SOH\n\
\\EOTType\DC2\b\n\
\\EOTNone\DLE\NUL\DC2\n\
\\n\
\\ACKString\DLE\SOH\DC2\b\n\
\\EOTJson\DLE\STX\DC2\f\n\
\\bProtobuf\DLE\ETX\DC2\b\n\
\\EOTAvro\DLE\EOT\DC2\b\n\
\\EOTBool\DLE\ENQ\DC2\b\n\
\\EOTInt8\DLE\ACK\DC2\t\n\
\\ENQInt16\DLE\a\DC2\t\n\
\\ENQInt32\DLE\b\DC2\t\n\
\\ENQInt64\DLE\t\DC2\t\n\
\\ENQFloat\DLE\n\
\\DC2\n\
\\n\
\\ACKDouble\DLE\v\DC2\b\n\
\\EOTDate\DLE\f\DC2\b\n\
\\EOTTime\DLE\r\DC2\r\n\
\\tTimestamp\DLE\SO\DC2\f\n\
\\bKeyValue\DLE\SI"
packedFileDescriptor :: Proxy Schema -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor Schema)
fieldsByTag
= let
name__field_descriptor :: FieldDescriptor Schema
name__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor Schema Text
-> FieldDescriptor Schema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"name"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens Schema Schema Text Text -> FieldAccessor Schema Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name")) ::
Data.ProtoLens.FieldDescriptor Schema
schemaData__field_descriptor :: FieldDescriptor Schema
schemaData__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Schema ByteString
-> FieldDescriptor Schema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"schema_data"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(WireDefault ByteString
-> Lens Schema Schema ByteString ByteString
-> FieldAccessor Schema ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ByteString
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "schemaData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaData")) ::
Data.ProtoLens.FieldDescriptor Schema
type'__field_descriptor :: FieldDescriptor Schema
type'__field_descriptor
= String
-> FieldTypeDescriptor Schema'Type
-> FieldAccessor Schema Schema'Type
-> FieldDescriptor Schema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"type"
(ScalarField Schema'Type -> FieldTypeDescriptor Schema'Type
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Schema'Type
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
Data.ProtoLens.FieldTypeDescriptor Schema'Type)
(WireDefault Schema'Type
-> Lens Schema Schema Schema'Type Schema'Type
-> FieldAccessor Schema Schema'Type
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Schema'Type
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'")) ::
Data.ProtoLens.FieldDescriptor Schema
properties__field_descriptor :: FieldDescriptor Schema
properties__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor Schema KeyValue
-> FieldDescriptor Schema
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"properties"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing -> Lens' Schema [KeyValue] -> FieldAccessor Schema KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"properties")) ::
Data.ProtoLens.FieldDescriptor Schema
in
[(Tag, FieldDescriptor Schema)] -> Map Tag (FieldDescriptor Schema)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor Schema
name__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor Schema
schemaData__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor Schema
type'__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor Schema
properties__field_descriptor)]
unknownFields :: LensLike' f Schema FieldSet
unknownFields
= (Schema -> FieldSet)
-> (Schema -> FieldSet -> Schema) -> Lens' Schema FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Schema -> FieldSet
_Schema'_unknownFields
(\ x__ :: Schema
x__ y__ :: FieldSet
y__ -> Schema
x__ {_Schema'_unknownFields :: FieldSet
_Schema'_unknownFields = FieldSet
y__})
defMessage :: Schema
defMessage
= $WSchema'_constructor :: Text
-> ByteString
-> Schema'Type
-> Vector KeyValue
-> FieldSet
-> Schema
Schema'_constructor
{_Schema'name :: Text
_Schema'name = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_Schema'schemaData :: ByteString
_Schema'schemaData = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_Schema'type' :: Schema'Type
_Schema'type' = Schema'Type
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_Schema'properties :: Vector KeyValue
_Schema'properties = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_Schema'_unknownFields :: FieldSet
_Schema'_unknownFields = []}
parseMessage :: Parser Schema
parseMessage
= let
loop ::
Schema
-> Prelude.Bool
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Bytes.Parser Schema
loop :: Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
x :: Schema
x
required'name :: Bool
required'name
required'schemaData :: Bool
required'schemaData
required'type' :: Bool
required'type'
mutable'properties :: Growing Vector RealWorld KeyValue
mutable'properties
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector KeyValue
frozen'properties <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties)
(let
missing :: [String]
missing
= (if Bool
required'name then (:) "name" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'schemaData then (:) "schema_data" else [String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'type' then (:) "type" else [String] -> [String]
forall a. a -> a
Prelude.id) []))
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
Schema -> Parser Schema
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter Schema Schema FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Schema -> Schema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter Schema Schema FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter Schema Schema (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> Schema -> Schema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties")
Vector KeyValue
frozen'properties
Schema
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"name"
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
(Setter Schema Schema Text Text -> Text -> Schema -> Schema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Text
y Schema
x)
Bool
Prelude.False
Bool
required'schemaData
Bool
required'type'
Growing Vector RealWorld KeyValue
mutable'properties
26
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"schema_data"
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
(Setter Schema Schema ByteString ByteString
-> ByteString -> Schema -> Schema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schemaData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaData") ByteString
y Schema
x)
Bool
required'name
Bool
Prelude.False
Bool
required'type'
Growing Vector RealWorld KeyValue
mutable'properties
32
-> do Schema'Type
y <- Parser Schema'Type -> String -> Parser Schema'Type
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Int -> Schema'Type) -> Parser Int -> Parser Schema'Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Int -> Schema'Type
forall a. Enum a => Int -> a
Prelude.toEnum
((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
"type"
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
(Setter Schema Schema Schema'Type Schema'Type
-> Schema'Type -> Schema -> Schema
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'") Schema'Type
y Schema
x)
Bool
required'name
Bool
required'schemaData
Bool
Prelude.False
Growing Vector RealWorld KeyValue
mutable'properties
42
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"properties"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties KeyValue
y)
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop Schema
x Bool
required'name Bool
required'schemaData Bool
required'type' Growing Vector RealWorld KeyValue
v
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
(Setter Schema Schema FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Schema -> Schema
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter Schema Schema FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Schema
x)
Bool
required'name
Bool
required'schemaData
Bool
required'type'
Growing Vector RealWorld KeyValue
mutable'properties
in
Parser Schema -> String -> Parser Schema
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld KeyValue
mutable'properties <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
Schema
-> Bool
-> Bool
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser Schema
loop
Schema
forall msg. Message msg => msg
Data.ProtoLens.defMessage
Bool
Prelude.True
Bool
Prelude.True
Bool
Prelude.True
Growing Vector RealWorld KeyValue
mutable'properties)
"Schema"
buildMessage :: Schema -> Builder
buildMessage
= \ _x :: Schema
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text Schema Schema Text Text -> Schema -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Schema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 26)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
(FoldLike ByteString Schema Schema ByteString ByteString
-> Schema -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "schemaData" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaData") Schema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Int -> Builder) -> (Schema'Type -> Int) -> Schema'Type -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
Schema'Type -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum
(FoldLike Schema'Type Schema Schema Schema'Type Schema'Type
-> Schema -> Schema'Type
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "type'" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"type'") Schema
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 42)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue) Schema Schema (Vector KeyValue) (Vector KeyValue)
-> Schema -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties") Schema
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet Schema Schema FieldSet FieldSet
-> Schema -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet Schema Schema FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields Schema
_x)))))
instance Control.DeepSeq.NFData Schema where
rnf :: Schema -> ()
rnf
= \ x__ :: Schema
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Schema -> FieldSet
_Schema'_unknownFields Schema
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Schema -> Text
_Schema'name Schema
x__)
(ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Schema -> ByteString
_Schema'schemaData Schema
x__)
(Schema'Type -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Schema -> Schema'Type
_Schema'type' Schema
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (Schema -> Vector KeyValue
_Schema'properties Schema
x__) ()))))
data Schema'Type
= Schema'None |
Schema'String |
Schema'Json |
Schema'Protobuf |
Schema'Avro |
Schema'Bool |
Schema'Int8 |
Schema'Int16 |
Schema'Int32 |
Schema'Int64 |
Schema'Float |
Schema'Double |
Schema'Date |
Schema'Time |
Schema'Timestamp |
Schema'KeyValue
deriving stock (Int -> Schema'Type -> ShowS
[Schema'Type] -> ShowS
Schema'Type -> String
(Int -> Schema'Type -> ShowS)
-> (Schema'Type -> String)
-> ([Schema'Type] -> ShowS)
-> Show Schema'Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Schema'Type] -> ShowS
$cshowList :: [Schema'Type] -> ShowS
show :: Schema'Type -> String
$cshow :: Schema'Type -> String
showsPrec :: Int -> Schema'Type -> ShowS
$cshowsPrec :: Int -> Schema'Type -> ShowS
Prelude.Show, Schema'Type -> Schema'Type -> Bool
(Schema'Type -> Schema'Type -> Bool)
-> (Schema'Type -> Schema'Type -> Bool) -> Eq Schema'Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Schema'Type -> Schema'Type -> Bool
$c/= :: Schema'Type -> Schema'Type -> Bool
== :: Schema'Type -> Schema'Type -> Bool
$c== :: Schema'Type -> Schema'Type -> Bool
Prelude.Eq, Eq Schema'Type
Eq Schema'Type =>
(Schema'Type -> Schema'Type -> Ordering)
-> (Schema'Type -> Schema'Type -> Bool)
-> (Schema'Type -> Schema'Type -> Bool)
-> (Schema'Type -> Schema'Type -> Bool)
-> (Schema'Type -> Schema'Type -> Bool)
-> (Schema'Type -> Schema'Type -> Schema'Type)
-> (Schema'Type -> Schema'Type -> Schema'Type)
-> Ord Schema'Type
Schema'Type -> Schema'Type -> Bool
Schema'Type -> Schema'Type -> Ordering
Schema'Type -> Schema'Type -> Schema'Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Schema'Type -> Schema'Type -> Schema'Type
$cmin :: Schema'Type -> Schema'Type -> Schema'Type
max :: Schema'Type -> Schema'Type -> Schema'Type
$cmax :: Schema'Type -> Schema'Type -> Schema'Type
>= :: Schema'Type -> Schema'Type -> Bool
$c>= :: Schema'Type -> Schema'Type -> Bool
> :: Schema'Type -> Schema'Type -> Bool
$c> :: Schema'Type -> Schema'Type -> Bool
<= :: Schema'Type -> Schema'Type -> Bool
$c<= :: Schema'Type -> Schema'Type -> Bool
< :: Schema'Type -> Schema'Type -> Bool
$c< :: Schema'Type -> Schema'Type -> Bool
compare :: Schema'Type -> Schema'Type -> Ordering
$ccompare :: Schema'Type -> Schema'Type -> Ordering
$cp1Ord :: Eq Schema'Type
Prelude.Ord)
instance Data.ProtoLens.MessageEnum Schema'Type where
maybeToEnum :: Int -> Maybe Schema'Type
maybeToEnum 0 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'None
maybeToEnum 1 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'String
maybeToEnum 2 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Json
maybeToEnum 3 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Protobuf
maybeToEnum 4 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Avro
maybeToEnum 5 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Bool
maybeToEnum 6 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int8
maybeToEnum 7 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int16
maybeToEnum 8 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int32
maybeToEnum 9 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int64
maybeToEnum 10 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Float
maybeToEnum 11 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Double
maybeToEnum 12 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Date
maybeToEnum 13 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Time
maybeToEnum 14 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Timestamp
maybeToEnum 15 = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'KeyValue
maybeToEnum _ = Maybe Schema'Type
forall a. Maybe a
Prelude.Nothing
showEnum :: Schema'Type -> String
showEnum Schema'None = "None"
showEnum Schema'String = "String"
showEnum Schema'Json = "Json"
showEnum Schema'Protobuf = "Protobuf"
showEnum Schema'Avro = "Avro"
showEnum Schema'Bool = "Bool"
showEnum Schema'Int8 = "Int8"
showEnum Schema'Int16 = "Int16"
showEnum Schema'Int32 = "Int32"
showEnum Schema'Int64 = "Int64"
showEnum Schema'Float = "Float"
showEnum Schema'Double = "Double"
showEnum Schema'Date = "Date"
showEnum Schema'Time = "Time"
showEnum Schema'Timestamp = "Timestamp"
showEnum Schema'KeyValue = "KeyValue"
readEnum :: String -> Maybe Schema'Type
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "None" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'None
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "String" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'String
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Json" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Json
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Protobuf" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Protobuf
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Avro" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Avro
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Bool" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Bool
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Int8" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int8
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Int16" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int16
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Int32" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int32
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Int64" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Int64
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Float" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Float
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Double" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Double
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Date" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Date
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Time" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Time
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "Timestamp" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'Timestamp
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "KeyValue" = Schema'Type -> Maybe Schema'Type
forall a. a -> Maybe a
Prelude.Just Schema'Type
Schema'KeyValue
| Bool
Prelude.otherwise
= Maybe Int -> (Int -> Maybe Schema'Type) -> Maybe Schema'Type
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe Schema'Type
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded Schema'Type where
minBound :: Schema'Type
minBound = Schema'Type
Schema'None
maxBound :: Schema'Type
maxBound = Schema'Type
Schema'KeyValue
instance Prelude.Enum Schema'Type where
toEnum :: Int -> Schema'Type
toEnum k__ :: Int
k__
= Schema'Type
-> (Schema'Type -> Schema'Type) -> Maybe Schema'Type -> Schema'Type
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> Schema'Type
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum Type: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
Schema'Type -> Schema'Type
forall a. a -> a
Prelude.id
(Int -> Maybe Schema'Type
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: Schema'Type -> Int
fromEnum Schema'None = 0
fromEnum Schema'String = 1
fromEnum Schema'Json = 2
fromEnum Schema'Protobuf = 3
fromEnum Schema'Avro = 4
fromEnum Schema'Bool = 5
fromEnum Schema'Int8 = 6
fromEnum Schema'Int16 = 7
fromEnum Schema'Int32 = 8
fromEnum Schema'Int64 = 9
fromEnum Schema'Float = 10
fromEnum Schema'Double = 11
fromEnum Schema'Date = 12
fromEnum Schema'Time = 13
fromEnum Schema'Timestamp = 14
fromEnum Schema'KeyValue = 15
succ :: Schema'Type -> Schema'Type
succ Schema'KeyValue
= String -> Schema'Type
forall a. HasCallStack => String -> a
Prelude.error
"Schema'Type.succ: bad argument Schema'KeyValue. This value would be out of bounds."
succ Schema'None = Schema'Type
Schema'String
succ Schema'String = Schema'Type
Schema'Json
succ Schema'Json = Schema'Type
Schema'Protobuf
succ Schema'Protobuf = Schema'Type
Schema'Avro
succ Schema'Avro = Schema'Type
Schema'Bool
succ Schema'Bool = Schema'Type
Schema'Int8
succ Schema'Int8 = Schema'Type
Schema'Int16
succ Schema'Int16 = Schema'Type
Schema'Int32
succ Schema'Int32 = Schema'Type
Schema'Int64
succ Schema'Int64 = Schema'Type
Schema'Float
succ Schema'Float = Schema'Type
Schema'Double
succ Schema'Double = Schema'Type
Schema'Date
succ Schema'Date = Schema'Type
Schema'Time
succ Schema'Time = Schema'Type
Schema'Timestamp
succ Schema'Timestamp = Schema'Type
Schema'KeyValue
pred :: Schema'Type -> Schema'Type
pred Schema'None
= String -> Schema'Type
forall a. HasCallStack => String -> a
Prelude.error
"Schema'Type.pred: bad argument Schema'None. This value would be out of bounds."
pred Schema'String = Schema'Type
Schema'None
pred Schema'Json = Schema'Type
Schema'String
pred Schema'Protobuf = Schema'Type
Schema'Json
pred Schema'Avro = Schema'Type
Schema'Protobuf
pred Schema'Bool = Schema'Type
Schema'Avro
pred Schema'Int8 = Schema'Type
Schema'Bool
pred Schema'Int16 = Schema'Type
Schema'Int8
pred Schema'Int32 = Schema'Type
Schema'Int16
pred Schema'Int64 = Schema'Type
Schema'Int32
pred Schema'Float = Schema'Type
Schema'Int64
pred Schema'Double = Schema'Type
Schema'Float
pred Schema'Date = Schema'Type
Schema'Double
pred Schema'Time = Schema'Type
Schema'Date
pred Schema'Timestamp = Schema'Type
Schema'Time
pred Schema'KeyValue = Schema'Type
Schema'Timestamp
enumFrom :: Schema'Type -> [Schema'Type]
enumFrom = Schema'Type -> [Schema'Type]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: Schema'Type -> Schema'Type -> [Schema'Type]
enumFromTo = Schema'Type -> Schema'Type -> [Schema'Type]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: Schema'Type -> Schema'Type -> [Schema'Type]
enumFromThen = Schema'Type -> Schema'Type -> [Schema'Type]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: Schema'Type -> Schema'Type -> Schema'Type -> [Schema'Type]
enumFromThenTo = Schema'Type -> Schema'Type -> Schema'Type -> [Schema'Type]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault Schema'Type where
fieldDefault :: Schema'Type
fieldDefault = Schema'Type
Schema'None
instance Control.DeepSeq.NFData Schema'Type where
rnf :: Schema'Type -> ()
rnf x__ :: Schema'Type
x__ = Schema'Type -> () -> ()
forall a b. a -> b -> b
Prelude.seq Schema'Type
x__ ()
data ServerError
= UnknownError |
MetadataError |
PersistenceError |
AuthenticationError |
AuthorizationError |
ConsumerBusy |
ServiceNotReady |
ProducerBlockedQuotaExceededError |
ProducerBlockedQuotaExceededException |
ChecksumError |
UnsupportedVersionError |
TopicNotFound |
SubscriptionNotFound |
ConsumerNotFound |
TooManyRequests |
TopicTerminatedError |
ProducerBusy |
InvalidTopicName |
IncompatibleSchema |
ConsumerAssignError |
TransactionCoordinatorNotFound |
InvalidTxnStatus |
NotAllowedError
deriving stock (Int -> ServerError -> ShowS
[ServerError] -> ShowS
ServerError -> String
(Int -> ServerError -> ShowS)
-> (ServerError -> String)
-> ([ServerError] -> ShowS)
-> Show ServerError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerError] -> ShowS
$cshowList :: [ServerError] -> ShowS
show :: ServerError -> String
$cshow :: ServerError -> String
showsPrec :: Int -> ServerError -> ShowS
$cshowsPrec :: Int -> ServerError -> ShowS
Prelude.Show, ServerError -> ServerError -> Bool
(ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> Bool) -> Eq ServerError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerError -> ServerError -> Bool
$c/= :: ServerError -> ServerError -> Bool
== :: ServerError -> ServerError -> Bool
$c== :: ServerError -> ServerError -> Bool
Prelude.Eq, Eq ServerError
Eq ServerError =>
(ServerError -> ServerError -> Ordering)
-> (ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> ServerError)
-> (ServerError -> ServerError -> ServerError)
-> Ord ServerError
ServerError -> ServerError -> Bool
ServerError -> ServerError -> Ordering
ServerError -> ServerError -> ServerError
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ServerError -> ServerError -> ServerError
$cmin :: ServerError -> ServerError -> ServerError
max :: ServerError -> ServerError -> ServerError
$cmax :: ServerError -> ServerError -> ServerError
>= :: ServerError -> ServerError -> Bool
$c>= :: ServerError -> ServerError -> Bool
> :: ServerError -> ServerError -> Bool
$c> :: ServerError -> ServerError -> Bool
<= :: ServerError -> ServerError -> Bool
$c<= :: ServerError -> ServerError -> Bool
< :: ServerError -> ServerError -> Bool
$c< :: ServerError -> ServerError -> Bool
compare :: ServerError -> ServerError -> Ordering
$ccompare :: ServerError -> ServerError -> Ordering
$cp1Ord :: Eq ServerError
Prelude.Ord)
instance Data.ProtoLens.MessageEnum ServerError where
maybeToEnum :: Int -> Maybe ServerError
maybeToEnum 0 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
UnknownError
maybeToEnum 1 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
MetadataError
maybeToEnum 2 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
PersistenceError
maybeToEnum 3 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
AuthenticationError
maybeToEnum 4 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
AuthorizationError
maybeToEnum 5 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerBusy
maybeToEnum 6 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ServiceNotReady
maybeToEnum 7 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBlockedQuotaExceededError
maybeToEnum 8 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBlockedQuotaExceededException
maybeToEnum 9 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ChecksumError
maybeToEnum 10 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
UnsupportedVersionError
maybeToEnum 11 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TopicNotFound
maybeToEnum 12 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
SubscriptionNotFound
maybeToEnum 13 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerNotFound
maybeToEnum 14 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TooManyRequests
maybeToEnum 15 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TopicTerminatedError
maybeToEnum 16 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBusy
maybeToEnum 17 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
InvalidTopicName
maybeToEnum 18 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
IncompatibleSchema
maybeToEnum 19 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerAssignError
maybeToEnum 20 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TransactionCoordinatorNotFound
maybeToEnum 21 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
InvalidTxnStatus
maybeToEnum 22 = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
NotAllowedError
maybeToEnum _ = Maybe ServerError
forall a. Maybe a
Prelude.Nothing
showEnum :: ServerError -> String
showEnum UnknownError = "UnknownError"
showEnum MetadataError = "MetadataError"
showEnum PersistenceError = "PersistenceError"
showEnum AuthenticationError = "AuthenticationError"
showEnum AuthorizationError = "AuthorizationError"
showEnum ConsumerBusy = "ConsumerBusy"
showEnum ServiceNotReady = "ServiceNotReady"
showEnum ProducerBlockedQuotaExceededError
= "ProducerBlockedQuotaExceededError"
showEnum ProducerBlockedQuotaExceededException
= "ProducerBlockedQuotaExceededException"
showEnum ChecksumError = "ChecksumError"
showEnum UnsupportedVersionError = "UnsupportedVersionError"
showEnum TopicNotFound = "TopicNotFound"
showEnum SubscriptionNotFound = "SubscriptionNotFound"
showEnum ConsumerNotFound = "ConsumerNotFound"
showEnum TooManyRequests = "TooManyRequests"
showEnum TopicTerminatedError = "TopicTerminatedError"
showEnum ProducerBusy = "ProducerBusy"
showEnum InvalidTopicName = "InvalidTopicName"
showEnum IncompatibleSchema = "IncompatibleSchema"
showEnum ConsumerAssignError = "ConsumerAssignError"
showEnum TransactionCoordinatorNotFound
= "TransactionCoordinatorNotFound"
showEnum InvalidTxnStatus = "InvalidTxnStatus"
showEnum NotAllowedError = "NotAllowedError"
readEnum :: String -> Maybe ServerError
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "UnknownError" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
UnknownError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "MetadataError" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
MetadataError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "PersistenceError" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
PersistenceError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AuthenticationError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
AuthenticationError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "AuthorizationError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
AuthorizationError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ConsumerBusy" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerBusy
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ServiceNotReady" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ServiceNotReady
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ProducerBlockedQuotaExceededError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBlockedQuotaExceededError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ProducerBlockedQuotaExceededException"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBlockedQuotaExceededException
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ChecksumError" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ChecksumError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "UnsupportedVersionError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
UnsupportedVersionError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "TopicNotFound" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TopicNotFound
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "SubscriptionNotFound"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
SubscriptionNotFound
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ConsumerNotFound" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerNotFound
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "TooManyRequests" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TooManyRequests
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "TopicTerminatedError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TopicTerminatedError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ProducerBusy" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ProducerBusy
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "InvalidTopicName" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
InvalidTopicName
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "IncompatibleSchema"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
IncompatibleSchema
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ConsumerAssignError"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
ConsumerAssignError
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "TransactionCoordinatorNotFound"
= ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
TransactionCoordinatorNotFound
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "InvalidTxnStatus" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
InvalidTxnStatus
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "NotAllowedError" = ServerError -> Maybe ServerError
forall a. a -> Maybe a
Prelude.Just ServerError
NotAllowedError
| Bool
Prelude.otherwise
= Maybe Int -> (Int -> Maybe ServerError) -> Maybe ServerError
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe ServerError
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded ServerError where
minBound :: ServerError
minBound = ServerError
UnknownError
maxBound :: ServerError
maxBound = ServerError
NotAllowedError
instance Prelude.Enum ServerError where
toEnum :: Int -> ServerError
toEnum k__ :: Int
k__
= ServerError
-> (ServerError -> ServerError) -> Maybe ServerError -> ServerError
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> ServerError
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum ServerError: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
ServerError -> ServerError
forall a. a -> a
Prelude.id
(Int -> Maybe ServerError
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: ServerError -> Int
fromEnum UnknownError = 0
fromEnum MetadataError = 1
fromEnum PersistenceError = 2
fromEnum AuthenticationError = 3
fromEnum AuthorizationError = 4
fromEnum ConsumerBusy = 5
fromEnum ServiceNotReady = 6
fromEnum ProducerBlockedQuotaExceededError = 7
fromEnum ProducerBlockedQuotaExceededException = 8
fromEnum ChecksumError = 9
fromEnum UnsupportedVersionError = 10
fromEnum TopicNotFound = 11
fromEnum SubscriptionNotFound = 12
fromEnum ConsumerNotFound = 13
fromEnum TooManyRequests = 14
fromEnum TopicTerminatedError = 15
fromEnum ProducerBusy = 16
fromEnum InvalidTopicName = 17
fromEnum IncompatibleSchema = 18
fromEnum ConsumerAssignError = 19
fromEnum TransactionCoordinatorNotFound = 20
fromEnum InvalidTxnStatus = 21
fromEnum NotAllowedError = 22
succ :: ServerError -> ServerError
succ NotAllowedError
= String -> ServerError
forall a. HasCallStack => String -> a
Prelude.error
"ServerError.succ: bad argument NotAllowedError. This value would be out of bounds."
succ UnknownError = ServerError
MetadataError
succ MetadataError = ServerError
PersistenceError
succ PersistenceError = ServerError
AuthenticationError
succ AuthenticationError = ServerError
AuthorizationError
succ AuthorizationError = ServerError
ConsumerBusy
succ ConsumerBusy = ServerError
ServiceNotReady
succ ServiceNotReady = ServerError
ProducerBlockedQuotaExceededError
succ ProducerBlockedQuotaExceededError
= ServerError
ProducerBlockedQuotaExceededException
succ ProducerBlockedQuotaExceededException = ServerError
ChecksumError
succ ChecksumError = ServerError
UnsupportedVersionError
succ UnsupportedVersionError = ServerError
TopicNotFound
succ TopicNotFound = ServerError
SubscriptionNotFound
succ SubscriptionNotFound = ServerError
ConsumerNotFound
succ ConsumerNotFound = ServerError
TooManyRequests
succ TooManyRequests = ServerError
TopicTerminatedError
succ TopicTerminatedError = ServerError
ProducerBusy
succ ProducerBusy = ServerError
InvalidTopicName
succ InvalidTopicName = ServerError
IncompatibleSchema
succ IncompatibleSchema = ServerError
ConsumerAssignError
succ ConsumerAssignError = ServerError
TransactionCoordinatorNotFound
succ TransactionCoordinatorNotFound = ServerError
InvalidTxnStatus
succ InvalidTxnStatus = ServerError
NotAllowedError
pred :: ServerError -> ServerError
pred UnknownError
= String -> ServerError
forall a. HasCallStack => String -> a
Prelude.error
"ServerError.pred: bad argument UnknownError. This value would be out of bounds."
pred MetadataError = ServerError
UnknownError
pred PersistenceError = ServerError
MetadataError
pred AuthenticationError = ServerError
PersistenceError
pred AuthorizationError = ServerError
AuthenticationError
pred ConsumerBusy = ServerError
AuthorizationError
pred ServiceNotReady = ServerError
ConsumerBusy
pred ProducerBlockedQuotaExceededError = ServerError
ServiceNotReady
pred ProducerBlockedQuotaExceededException
= ServerError
ProducerBlockedQuotaExceededError
pred ChecksumError = ServerError
ProducerBlockedQuotaExceededException
pred UnsupportedVersionError = ServerError
ChecksumError
pred TopicNotFound = ServerError
UnsupportedVersionError
pred SubscriptionNotFound = ServerError
TopicNotFound
pred ConsumerNotFound = ServerError
SubscriptionNotFound
pred TooManyRequests = ServerError
ConsumerNotFound
pred TopicTerminatedError = ServerError
TooManyRequests
pred ProducerBusy = ServerError
TopicTerminatedError
pred InvalidTopicName = ServerError
ProducerBusy
pred IncompatibleSchema = ServerError
InvalidTopicName
pred ConsumerAssignError = ServerError
IncompatibleSchema
pred TransactionCoordinatorNotFound = ServerError
ConsumerAssignError
pred InvalidTxnStatus = ServerError
TransactionCoordinatorNotFound
pred NotAllowedError = ServerError
InvalidTxnStatus
enumFrom :: ServerError -> [ServerError]
enumFrom = ServerError -> [ServerError]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: ServerError -> ServerError -> [ServerError]
enumFromTo = ServerError -> ServerError -> [ServerError]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: ServerError -> ServerError -> [ServerError]
enumFromThen = ServerError -> ServerError -> [ServerError]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: ServerError -> ServerError -> ServerError -> [ServerError]
enumFromThenTo = ServerError -> ServerError -> ServerError -> [ServerError]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault ServerError where
fieldDefault :: ServerError
fieldDefault = ServerError
UnknownError
instance Control.DeepSeq.NFData ServerError where
rnf :: ServerError -> ()
rnf x__ :: ServerError
x__ = ServerError -> () -> ()
forall a b. a -> b -> b
Prelude.seq ServerError
x__ ()
data SingleMessageMetadata
= SingleMessageMetadata'_constructor {SingleMessageMetadata -> Vector KeyValue
_SingleMessageMetadata'properties :: !(Data.Vector.Vector KeyValue),
SingleMessageMetadata -> Maybe Text
_SingleMessageMetadata'partitionKey :: !(Prelude.Maybe Data.Text.Text),
SingleMessageMetadata -> Int32
_SingleMessageMetadata'payloadSize :: !Data.Int.Int32,
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'compactedOut :: !(Prelude.Maybe Prelude.Bool),
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'eventTime :: !(Prelude.Maybe Data.Word.Word64),
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded :: !(Prelude.Maybe Prelude.Bool),
SingleMessageMetadata -> Maybe ByteString
_SingleMessageMetadata'orderingKey :: !(Prelude.Maybe Data.ByteString.ByteString),
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'sequenceId :: !(Prelude.Maybe Data.Word.Word64),
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullValue :: !(Prelude.Maybe Prelude.Bool),
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullPartitionKey :: !(Prelude.Maybe Prelude.Bool),
SingleMessageMetadata -> FieldSet
_SingleMessageMetadata'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (SingleMessageMetadata -> SingleMessageMetadata -> Bool
(SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> (SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> Eq SingleMessageMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c/= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
== :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c== :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
Prelude.Eq, Eq SingleMessageMetadata
Eq SingleMessageMetadata =>
(SingleMessageMetadata -> SingleMessageMetadata -> Ordering)
-> (SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> (SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> (SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> (SingleMessageMetadata -> SingleMessageMetadata -> Bool)
-> (SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata)
-> (SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata)
-> Ord SingleMessageMetadata
SingleMessageMetadata -> SingleMessageMetadata -> Bool
SingleMessageMetadata -> SingleMessageMetadata -> Ordering
SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata
$cmin :: SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata
max :: SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata
$cmax :: SingleMessageMetadata
-> SingleMessageMetadata -> SingleMessageMetadata
>= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c>= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
> :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c> :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
<= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c<= :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
< :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
$c< :: SingleMessageMetadata -> SingleMessageMetadata -> Bool
compare :: SingleMessageMetadata -> SingleMessageMetadata -> Ordering
$ccompare :: SingleMessageMetadata -> SingleMessageMetadata -> Ordering
$cp1Ord :: Eq SingleMessageMetadata
Prelude.Ord)
instance Prelude.Show SingleMessageMetadata where
showsPrec :: Int -> SingleMessageMetadata -> ShowS
showsPrec _ __x :: SingleMessageMetadata
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(SingleMessageMetadata -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort SingleMessageMetadata
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "properties" [KeyValue] where
fieldOf :: Proxy# "properties"
-> ([KeyValue] -> f [KeyValue])
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> (([KeyValue] -> f [KeyValue])
-> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Vector KeyValue)
-> (SingleMessageMetadata
-> Vector KeyValue -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Vector KeyValue)
(Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Vector KeyValue
_SingleMessageMetadata'properties
(\ x__ :: SingleMessageMetadata
x__ y__ :: Vector KeyValue
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'properties :: Vector KeyValue
_SingleMessageMetadata'properties = Vector KeyValue
y__}))
((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ _ y__ :: [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "vec'properties" (Data.Vector.Vector KeyValue) where
fieldOf :: Proxy# "vec'properties"
-> (Vector KeyValue -> f (Vector KeyValue))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Vector KeyValue -> f (Vector KeyValue))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Vector KeyValue)
-> (SingleMessageMetadata
-> Vector KeyValue -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Vector KeyValue)
(Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Vector KeyValue
_SingleMessageMetadata'properties
(\ x__ :: SingleMessageMetadata
x__ y__ :: Vector KeyValue
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'properties :: Vector KeyValue
_SingleMessageMetadata'properties = Vector KeyValue
y__}))
(Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "partitionKey" Data.Text.Text where
fieldOf :: Proxy# "partitionKey"
-> (Text -> f Text)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> (Text -> f Text)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Text)
-> (SingleMessageMetadata -> Maybe Text -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Text
_SingleMessageMetadata'partitionKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Text
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'partitionKey :: Maybe Text
_SingleMessageMetadata'partitionKey = Maybe Text
y__}))
(Text -> Lens' (Maybe Text) Text
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'partitionKey" (Prelude.Maybe Data.Text.Text) where
fieldOf :: Proxy# "maybe'partitionKey"
-> (Maybe Text -> f (Maybe Text))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Text -> f (Maybe Text))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text))
-> (Maybe Text -> f (Maybe Text))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Text)
-> (SingleMessageMetadata -> Maybe Text -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Text)
(Maybe Text)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Text
_SingleMessageMetadata'partitionKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Text
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'partitionKey :: Maybe Text
_SingleMessageMetadata'partitionKey = Maybe Text
y__}))
(Maybe Text -> f (Maybe Text)) -> Maybe Text -> f (Maybe Text)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "payloadSize" Data.Int.Int32 where
fieldOf :: Proxy# "payloadSize"
-> (Int32 -> f Int32)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Int32 -> f Int32)
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Int32 -> f Int32) -> Int32 -> f Int32)
-> (Int32 -> f Int32)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Int32)
-> (SingleMessageMetadata -> Int32 -> SingleMessageMetadata)
-> Lens SingleMessageMetadata SingleMessageMetadata Int32 Int32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Int32
_SingleMessageMetadata'payloadSize
(\ x__ :: SingleMessageMetadata
x__ y__ :: Int32
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'payloadSize :: Int32
_SingleMessageMetadata'payloadSize = Int32
y__}))
(Int32 -> f Int32) -> Int32 -> f Int32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "compactedOut" Prelude.Bool where
fieldOf :: Proxy# "compactedOut"
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'compactedOut
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'compactedOut :: Maybe Bool
_SingleMessageMetadata'compactedOut = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'compactedOut" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'compactedOut"
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'compactedOut
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'compactedOut :: Maybe Bool
_SingleMessageMetadata'compactedOut = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "eventTime" Data.Word.Word64 where
fieldOf :: Proxy# "eventTime"
-> (Word64 -> f Word64)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Word64)
-> (SingleMessageMetadata -> Maybe Word64 -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'eventTime
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Word64
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'eventTime :: Maybe Word64
_SingleMessageMetadata'eventTime = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens 0)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'eventTime" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'eventTime"
-> (Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Word64)
-> (SingleMessageMetadata -> Maybe Word64 -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'eventTime
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Word64
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'eventTime :: Maybe Word64
_SingleMessageMetadata'eventTime = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "partitionKeyB64Encoded" Prelude.Bool where
fieldOf :: Proxy# "partitionKeyB64Encoded"
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__
-> SingleMessageMetadata
x__ {_SingleMessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'partitionKeyB64Encoded" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'partitionKeyB64Encoded"
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__
-> SingleMessageMetadata
x__ {_SingleMessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "orderingKey" Data.ByteString.ByteString where
fieldOf :: Proxy# "orderingKey"
-> (ByteString -> f ByteString)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((ByteString -> f ByteString)
-> Maybe ByteString -> f (Maybe ByteString))
-> (ByteString -> f ByteString)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe ByteString)
-> (SingleMessageMetadata
-> Maybe ByteString -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe ByteString
_SingleMessageMetadata'orderingKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe ByteString
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'orderingKey :: Maybe ByteString
_SingleMessageMetadata'orderingKey = Maybe ByteString
y__}))
(ByteString -> Lens' (Maybe ByteString) ByteString
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'orderingKey" (Prelude.Maybe Data.ByteString.ByteString) where
fieldOf :: Proxy# "maybe'orderingKey"
-> (Maybe ByteString -> f (Maybe ByteString))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe ByteString -> f (Maybe ByteString))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString))
-> (Maybe ByteString -> f (Maybe ByteString))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe ByteString)
-> (SingleMessageMetadata
-> Maybe ByteString -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe ByteString)
(Maybe ByteString)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe ByteString
_SingleMessageMetadata'orderingKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe ByteString
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'orderingKey :: Maybe ByteString
_SingleMessageMetadata'orderingKey = Maybe ByteString
y__}))
(Maybe ByteString -> f (Maybe ByteString))
-> Maybe ByteString -> f (Maybe ByteString)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "sequenceId" Data.Word.Word64 where
fieldOf :: Proxy# "sequenceId"
-> (Word64 -> f Word64)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Word64 -> f Word64) -> Maybe Word64 -> f (Maybe Word64))
-> (Word64 -> f Word64)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Word64)
-> (SingleMessageMetadata -> Maybe Word64 -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'sequenceId
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Word64
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'sequenceId :: Maybe Word64
_SingleMessageMetadata'sequenceId = Maybe Word64
y__}))
(Word64 -> Lens' (Maybe Word64) Word64
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'sequenceId" (Prelude.Maybe Data.Word.Word64) where
fieldOf :: Proxy# "maybe'sequenceId"
-> (Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64))
-> (Maybe Word64 -> f (Maybe Word64))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Word64)
-> (SingleMessageMetadata -> Maybe Word64 -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'sequenceId
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Word64
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'sequenceId :: Maybe Word64
_SingleMessageMetadata'sequenceId = Maybe Word64
y__}))
(Maybe Word64 -> f (Maybe Word64))
-> Maybe Word64 -> f (Maybe Word64)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "nullValue" Prelude.Bool where
fieldOf :: Proxy# "nullValue"
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullValue
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'nullValue :: Maybe Bool
_SingleMessageMetadata'nullValue = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'nullValue" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'nullValue"
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullValue
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'nullValue :: Maybe Bool
_SingleMessageMetadata'nullValue = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "nullPartitionKey" Prelude.Bool where
fieldOf :: Proxy# "nullPartitionKey"
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Bool -> f Bool) -> Maybe Bool -> f (Maybe Bool))
-> (Bool -> f Bool)
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullPartitionKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'nullPartitionKey :: Maybe Bool
_SingleMessageMetadata'nullPartitionKey = Maybe Bool
y__}))
(Bool -> Lens' (Maybe Bool) Bool
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Bool
Prelude.False)
instance Data.ProtoLens.Field.HasField SingleMessageMetadata "maybe'nullPartitionKey" (Prelude.Maybe Prelude.Bool) where
fieldOf :: Proxy# "maybe'nullPartitionKey"
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
fieldOf _
= ((Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata -> f SingleMessageMetadata)
-> ((Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool))
-> (Maybe Bool -> f (Maybe Bool))
-> SingleMessageMetadata
-> f SingleMessageMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((SingleMessageMetadata -> Maybe Bool)
-> (SingleMessageMetadata -> Maybe Bool -> SingleMessageMetadata)
-> Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullPartitionKey
(\ x__ :: SingleMessageMetadata
x__ y__ :: Maybe Bool
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'nullPartitionKey :: Maybe Bool
_SingleMessageMetadata'nullPartitionKey = Maybe Bool
y__}))
(Maybe Bool -> f (Maybe Bool)) -> Maybe Bool -> f (Maybe Bool)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message SingleMessageMetadata where
messageName :: Proxy SingleMessageMetadata -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.SingleMessageMetadata"
packedMessageDescriptor :: Proxy SingleMessageMetadata -> ByteString
packedMessageDescriptor _
= "\n\
\\NAKSingleMessageMetadata\DC26\n\
\\n\
\properties\CAN\SOH \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\DC2#\n\
\\rpartition_key\CAN\STX \SOH(\tR\fpartitionKey\DC2!\n\
\\fpayload_size\CAN\ETX \STX(\ENQR\vpayloadSize\DC2*\n\
\\rcompacted_out\CAN\EOT \SOH(\b:\ENQfalseR\fcompactedOut\DC2 \n\
\\n\
\event_time\CAN\ENQ \SOH(\EOT:\SOH0R\teventTime\DC2@\n\
\\EMpartition_key_b64_encoded\CAN\ACK \SOH(\b:\ENQfalseR\SYNpartitionKeyB64Encoded\DC2!\n\
\\fordering_key\CAN\a \SOH(\fR\vorderingKey\DC2\US\n\
\\vsequence_id\CAN\b \SOH(\EOTR\n\
\sequenceId\DC2$\n\
\\n\
\null_value\CAN\t \SOH(\b:\ENQfalseR\tnullValue\DC23\n\
\\DC2null_partition_key\CAN\n\
\ \SOH(\b:\ENQfalseR\DLEnullPartitionKey"
packedFileDescriptor :: Proxy SingleMessageMetadata -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor SingleMessageMetadata)
fieldsByTag
= let
properties__field_descriptor :: FieldDescriptor SingleMessageMetadata
properties__field_descriptor
= String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor SingleMessageMetadata KeyValue
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"properties"
(MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor KeyValue)
(Packing
-> Lens' SingleMessageMetadata [KeyValue]
-> FieldAccessor SingleMessageMetadata KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall s a (f :: * -> *).
(HasField s "properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"properties")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
partitionKey__field_descriptor :: FieldDescriptor SingleMessageMetadata
partitionKey__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor SingleMessageMetadata Text
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partition_key"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Text)
(Maybe Text)
-> FieldAccessor SingleMessageMetadata Text
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKey")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
payloadSize__field_descriptor :: FieldDescriptor SingleMessageMetadata
payloadSize__field_descriptor
= String
-> FieldTypeDescriptor Int32
-> FieldAccessor SingleMessageMetadata Int32
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"payload_size"
(ScalarField Int32 -> FieldTypeDescriptor Int32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Int32
Data.ProtoLens.Int32Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Int.Int32)
(WireDefault Int32
-> Lens SingleMessageMetadata SingleMessageMetadata Int32 Int32
-> FieldAccessor SingleMessageMetadata Int32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Int32
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "payloadSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"payloadSize")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
compactedOut__field_descriptor :: FieldDescriptor SingleMessageMetadata
compactedOut__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor SingleMessageMetadata Bool
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"compacted_out"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor SingleMessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'compactedOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'compactedOut")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
eventTime__field_descriptor :: FieldDescriptor SingleMessageMetadata
eventTime__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor SingleMessageMetadata Word64
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"event_time"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor SingleMessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'eventTime")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
partitionKeyB64Encoded__field_descriptor :: FieldDescriptor SingleMessageMetadata
partitionKeyB64Encoded__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor SingleMessageMetadata Bool
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"partition_key_b64_encoded"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor SingleMessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKeyB64Encoded")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
orderingKey__field_descriptor :: FieldDescriptor SingleMessageMetadata
orderingKey__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor SingleMessageMetadata ByteString
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"ordering_key"
(ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> FieldAccessor SingleMessageMetadata ByteString
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'orderingKey")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
sequenceId__field_descriptor :: FieldDescriptor SingleMessageMetadata
sequenceId__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor SingleMessageMetadata Word64
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"sequence_id"
(ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.UInt64Field ::
Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
-> FieldAccessor SingleMessageMetadata Word64
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sequenceId")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
nullValue__field_descriptor :: FieldDescriptor SingleMessageMetadata
nullValue__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor SingleMessageMetadata Bool
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"null_value"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor SingleMessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nullValue")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
nullPartitionKey__field_descriptor :: FieldDescriptor SingleMessageMetadata
nullPartitionKey__field_descriptor
= String
-> FieldTypeDescriptor Bool
-> FieldAccessor SingleMessageMetadata Bool
-> FieldDescriptor SingleMessageMetadata
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"null_partition_key"
(ScalarField Bool -> FieldTypeDescriptor Bool
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Bool
Data.ProtoLens.BoolField ::
Data.ProtoLens.FieldTypeDescriptor Prelude.Bool)
(Lens
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> FieldAccessor SingleMessageMetadata Bool
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall s a (f :: * -> *).
(HasField s "maybe'nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nullPartitionKey")) ::
Data.ProtoLens.FieldDescriptor SingleMessageMetadata
in
[(Tag, FieldDescriptor SingleMessageMetadata)]
-> Map Tag (FieldDescriptor SingleMessageMetadata)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor SingleMessageMetadata
properties__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor SingleMessageMetadata
partitionKey__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 3, FieldDescriptor SingleMessageMetadata
payloadSize__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 4, FieldDescriptor SingleMessageMetadata
compactedOut__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 5, FieldDescriptor SingleMessageMetadata
eventTime__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 6, FieldDescriptor SingleMessageMetadata
partitionKeyB64Encoded__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 7, FieldDescriptor SingleMessageMetadata
orderingKey__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 8, FieldDescriptor SingleMessageMetadata
sequenceId__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 9, FieldDescriptor SingleMessageMetadata
nullValue__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 10, FieldDescriptor SingleMessageMetadata
nullPartitionKey__field_descriptor)]
unknownFields :: LensLike' f SingleMessageMetadata FieldSet
unknownFields
= (SingleMessageMetadata -> FieldSet)
-> (SingleMessageMetadata -> FieldSet -> SingleMessageMetadata)
-> Lens' SingleMessageMetadata FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
SingleMessageMetadata -> FieldSet
_SingleMessageMetadata'_unknownFields
(\ x__ :: SingleMessageMetadata
x__ y__ :: FieldSet
y__ -> SingleMessageMetadata
x__ {_SingleMessageMetadata'_unknownFields :: FieldSet
_SingleMessageMetadata'_unknownFields = FieldSet
y__})
defMessage :: SingleMessageMetadata
defMessage
= $WSingleMessageMetadata'_constructor :: Vector KeyValue
-> Maybe Text
-> Int32
-> Maybe Bool
-> Maybe Word64
-> Maybe Bool
-> Maybe ByteString
-> Maybe Word64
-> Maybe Bool
-> Maybe Bool
-> FieldSet
-> SingleMessageMetadata
SingleMessageMetadata'_constructor
{_SingleMessageMetadata'properties :: Vector KeyValue
_SingleMessageMetadata'properties = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_SingleMessageMetadata'partitionKey :: Maybe Text
_SingleMessageMetadata'partitionKey = Maybe Text
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'payloadSize :: Int32
_SingleMessageMetadata'payloadSize = Int32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_SingleMessageMetadata'compactedOut :: Maybe Bool
_SingleMessageMetadata'compactedOut = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'eventTime :: Maybe Word64
_SingleMessageMetadata'eventTime = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'partitionKeyB64Encoded :: Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'orderingKey :: Maybe ByteString
_SingleMessageMetadata'orderingKey = Maybe ByteString
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'sequenceId :: Maybe Word64
_SingleMessageMetadata'sequenceId = Maybe Word64
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'nullValue :: Maybe Bool
_SingleMessageMetadata'nullValue = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'nullPartitionKey :: Maybe Bool
_SingleMessageMetadata'nullPartitionKey = Maybe Bool
forall a. Maybe a
Prelude.Nothing,
_SingleMessageMetadata'_unknownFields :: FieldSet
_SingleMessageMetadata'_unknownFields = []}
parseMessage :: Parser SingleMessageMetadata
parseMessage
= let
loop ::
SingleMessageMetadata
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld KeyValue
-> Data.ProtoLens.Encoding.Bytes.Parser SingleMessageMetadata
loop :: SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop x :: SingleMessageMetadata
x required'payloadSize :: Bool
required'payloadSize mutable'properties :: Growing Vector RealWorld KeyValue
mutable'properties
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector KeyValue
frozen'properties <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties)
(let
missing :: [String]
missing
= (if Bool
required'payloadSize then (:) "payload_size" else [String] -> [String]
forall a. a -> a
Prelude.id)
[]
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
SingleMessageMetadata -> Parser SingleMessageMetadata
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter
SingleMessageMetadata SingleMessageMetadata FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> SingleMessageMetadata
-> SingleMessageMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
SingleMessageMetadata SingleMessageMetadata FieldSet FieldSet
Data.ProtoLens.unknownFields
(\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
SingleMessageMetadata
SingleMessageMetadata
(Vector KeyValue)
(Vector KeyValue)
-> Vector KeyValue
-> SingleMessageMetadata
-> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties")
Vector KeyValue
frozen'properties
SingleMessageMetadata
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
"properties"
Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'properties KeyValue
y)
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop SingleMessageMetadata
x Bool
required'payloadSize Growing Vector RealWorld KeyValue
v
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"partition_key"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Text Text
-> Text -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionKey") Text
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
24
-> do Int32
y <- Parser Int32 -> String -> Parser Int32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Int32) -> Parser Word64 -> Parser Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
Word64 -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"payload_size"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Int32 Int32
-> Int32 -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "payloadSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"payloadSize") Int32
y SingleMessageMetadata
x)
Bool
Prelude.False
Growing Vector RealWorld KeyValue
mutable'properties
32
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"compacted_out"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Bool Bool
-> Bool -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "compactedOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"compactedOut") Bool
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
40
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "event_time"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Word64 Word64
-> Word64 -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"eventTime") Word64
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
48
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"partition_key_b64_encoded"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Bool Bool
-> Bool -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"partitionKeyB64Encoded") Bool
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
58
-> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
"ordering_key"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter
SingleMessageMetadata SingleMessageMetadata ByteString ByteString
-> ByteString -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"orderingKey") ByteString
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
64
-> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt "sequence_id"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Word64 Word64
-> Word64 -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"sequenceId") Word64
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
72
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"null_value"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Bool Bool
-> Bool -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nullValue") Bool
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
80
-> do Bool
y <- Parser Bool -> String -> Parser Bool
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
((Word64 -> Bool) -> Parser Word64 -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
(Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude./=) 0) Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
"null_partition_key"
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter SingleMessageMetadata SingleMessageMetadata Bool Bool
-> Bool -> SingleMessageMetadata -> SingleMessageMetadata
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nullPartitionKey") Bool
y SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop
(Setter
SingleMessageMetadata SingleMessageMetadata FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> SingleMessageMetadata
-> SingleMessageMetadata
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter
SingleMessageMetadata SingleMessageMetadata FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) SingleMessageMetadata
x)
Bool
required'payloadSize
Growing Vector RealWorld KeyValue
mutable'properties
in
Parser SingleMessageMetadata
-> String -> Parser SingleMessageMetadata
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld KeyValue
mutable'properties <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
SingleMessageMetadata
-> Bool
-> Growing Vector RealWorld KeyValue
-> Parser SingleMessageMetadata
loop SingleMessageMetadata
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Growing Vector RealWorld KeyValue
mutable'properties)
"SingleMessageMetadata"
buildMessage :: SingleMessageMetadata -> Builder
buildMessage
= \ _x :: SingleMessageMetadata
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ _v :: KeyValue
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
KeyValue
_v))
(FoldLike
(Vector KeyValue)
SingleMessageMetadata
SingleMessageMetadata
(Vector KeyValue)
(Vector KeyValue)
-> SingleMessageMetadata -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "vec'properties" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'properties") SingleMessageMetadata
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Text)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Text)
(Maybe Text)
-> SingleMessageMetadata -> Maybe Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKey") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Text
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
Text
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 24)
((Word64 -> Builder) -> (Int32 -> Word64) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
Int32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(FoldLike
Int32 SingleMessageMetadata SingleMessageMetadata Int32 Int32
-> SingleMessageMetadata -> Int32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "payloadSize" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"payloadSize") SingleMessageMetadata
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> SingleMessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'compactedOut" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'compactedOut") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 32)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
-> SingleMessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'eventTime" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'eventTime") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 40)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> SingleMessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'partitionKeyB64Encoded" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'partitionKeyB64Encoded") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 48)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe ByteString)
SingleMessageMetadata
SingleMessageMetadata
(Maybe ByteString)
(Maybe ByteString)
-> SingleMessageMetadata -> Maybe ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'orderingKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'orderingKey") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: ByteString
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 58)
((\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
ByteString
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Word64)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Word64)
(Maybe Word64)
-> SingleMessageMetadata -> Maybe Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'sequenceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'sequenceId") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Word64
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 64)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> SingleMessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'nullValue" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nullValue") SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 72)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe Bool)
SingleMessageMetadata
SingleMessageMetadata
(Maybe Bool)
(Maybe Bool)
-> SingleMessageMetadata -> Maybe Bool
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "maybe'nullPartitionKey" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
@"maybe'nullPartitionKey")
SingleMessageMetadata
_x
of
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just _v :: Bool
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 80)
((Word64 -> Builder) -> (Bool -> Word64) -> Bool -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(\ b :: Bool
b -> if Bool
b then 1 else 0)
Bool
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet
SingleMessageMetadata
SingleMessageMetadata
FieldSet
FieldSet
-> SingleMessageMetadata -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
FoldLike
FieldSet
SingleMessageMetadata
SingleMessageMetadata
FieldSet
FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields SingleMessageMetadata
_x)))))))))))
instance Control.DeepSeq.NFData SingleMessageMetadata where
rnf :: SingleMessageMetadata -> ()
rnf
= \ x__ :: SingleMessageMetadata
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> FieldSet
_SingleMessageMetadata'_unknownFields SingleMessageMetadata
x__)
(Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Vector KeyValue
_SingleMessageMetadata'properties SingleMessageMetadata
x__)
(Maybe Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Text
_SingleMessageMetadata'partitionKey SingleMessageMetadata
x__)
(Int32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Int32
_SingleMessageMetadata'payloadSize SingleMessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'compactedOut SingleMessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'eventTime SingleMessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'partitionKeyB64Encoded SingleMessageMetadata
x__)
(Maybe ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe ByteString
_SingleMessageMetadata'orderingKey SingleMessageMetadata
x__)
(Maybe Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Word64
_SingleMessageMetadata'sequenceId SingleMessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullValue SingleMessageMetadata
x__)
(Maybe Bool -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(SingleMessageMetadata -> Maybe Bool
_SingleMessageMetadata'nullPartitionKey SingleMessageMetadata
x__)
()))))))))))
data Subscription
= Subscription'_constructor {Subscription -> Text
_Subscription'topic :: !Data.Text.Text,
Subscription -> Text
_Subscription'subscription :: !Data.Text.Text,
Subscription -> FieldSet
_Subscription'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (Subscription -> Subscription -> Bool
(Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Bool) -> Eq Subscription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subscription -> Subscription -> Bool
$c/= :: Subscription -> Subscription -> Bool
== :: Subscription -> Subscription -> Bool
$c== :: Subscription -> Subscription -> Bool
Prelude.Eq, Eq Subscription
Eq Subscription =>
(Subscription -> Subscription -> Ordering)
-> (Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Subscription)
-> (Subscription -> Subscription -> Subscription)
-> Ord Subscription
Subscription -> Subscription -> Bool
Subscription -> Subscription -> Ordering
Subscription -> Subscription -> Subscription
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Subscription -> Subscription -> Subscription
$cmin :: Subscription -> Subscription -> Subscription
max :: Subscription -> Subscription -> Subscription
$cmax :: Subscription -> Subscription -> Subscription
>= :: Subscription -> Subscription -> Bool
$c>= :: Subscription -> Subscription -> Bool
> :: Subscription -> Subscription -> Bool
$c> :: Subscription -> Subscription -> Bool
<= :: Subscription -> Subscription -> Bool
$c<= :: Subscription -> Subscription -> Bool
< :: Subscription -> Subscription -> Bool
$c< :: Subscription -> Subscription -> Bool
compare :: Subscription -> Subscription -> Ordering
$ccompare :: Subscription -> Subscription -> Ordering
$cp1Ord :: Eq Subscription
Prelude.Ord)
instance Prelude.Show Subscription where
showsPrec :: Int -> Subscription -> ShowS
showsPrec _ __x :: Subscription
__x __s :: String
__s
= Char -> ShowS
Prelude.showChar
'{'
(String -> ShowS
Prelude.showString
(Subscription -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Subscription
__x) (Char -> ShowS
Prelude.showChar '}' String
__s))
instance Data.ProtoLens.Field.HasField Subscription "topic" Data.Text.Text where
fieldOf :: Proxy# "topic"
-> (Text -> f Text) -> Subscription -> f Subscription
fieldOf _
= ((Text -> f Text) -> Subscription -> f Subscription)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Subscription
-> f Subscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Subscription -> Text)
-> (Subscription -> Text -> Subscription)
-> Lens Subscription Subscription Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Subscription -> Text
_Subscription'topic (\ x__ :: Subscription
x__ y__ :: Text
y__ -> Subscription
x__ {_Subscription'topic :: Text
_Subscription'topic = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Subscription "subscription" Data.Text.Text where
fieldOf :: Proxy# "subscription"
-> (Text -> f Text) -> Subscription -> f Subscription
fieldOf _
= ((Text -> f Text) -> Subscription -> f Subscription)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Subscription
-> f Subscription
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Subscription -> Text)
-> (Subscription -> Text -> Subscription)
-> Lens Subscription Subscription Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Subscription -> Text
_Subscription'subscription
(\ x__ :: Subscription
x__ y__ :: Text
y__ -> Subscription
x__ {_Subscription'subscription :: Text
_Subscription'subscription = Text
y__}))
(Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Subscription where
messageName :: Proxy Subscription -> Text
messageName _ = String -> Text
Data.Text.pack "pulsar.proto.Subscription"
packedMessageDescriptor :: Proxy Subscription -> ByteString
packedMessageDescriptor _
= "\n\
\\fSubscription\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\"\n\
\\fsubscription\CAN\STX \STX(\tR\fsubscription"
packedFileDescriptor :: Proxy Subscription -> ByteString
packedFileDescriptor _ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor Subscription)
fieldsByTag
= let
topic__field_descriptor :: FieldDescriptor Subscription
topic__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor Subscription Text
-> FieldDescriptor Subscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"topic"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens Subscription Subscription Text Text
-> FieldAccessor Subscription Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic")) ::
Data.ProtoLens.FieldDescriptor Subscription
subscription__field_descriptor :: FieldDescriptor Subscription
subscription__field_descriptor
= String
-> FieldTypeDescriptor Text
-> FieldAccessor Subscription Text
-> FieldDescriptor Subscription
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
"subscription"
(ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
(WireDefault Text
-> Lens Subscription Subscription Text Text
-> FieldAccessor Subscription Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Text
forall value. WireDefault value
Data.ProtoLens.Required
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription")) ::
Data.ProtoLens.FieldDescriptor Subscription
in
[(Tag, FieldDescriptor Subscription)]
-> Map Tag (FieldDescriptor Subscription)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag 1, FieldDescriptor Subscription
topic__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag 2, FieldDescriptor Subscription
subscription__field_descriptor)]
unknownFields :: LensLike' f Subscription FieldSet
unknownFields
= (Subscription -> FieldSet)
-> (Subscription -> FieldSet -> Subscription)
-> Lens' Subscription FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Subscription -> FieldSet
_Subscription'_unknownFields
(\ x__ :: Subscription
x__ y__ :: FieldSet
y__ -> Subscription
x__ {_Subscription'_unknownFields :: FieldSet
_Subscription'_unknownFields = FieldSet
y__})
defMessage :: Subscription
defMessage
= $WSubscription'_constructor :: Text -> Text -> FieldSet -> Subscription
Subscription'_constructor
{_Subscription'topic :: Text
_Subscription'topic = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_Subscription'subscription :: Text
_Subscription'subscription = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_Subscription'_unknownFields :: FieldSet
_Subscription'_unknownFields = []}
parseMessage :: Parser Subscription
parseMessage
= let
loop ::
Subscription
-> Prelude.Bool
-> Prelude.Bool
-> Data.ProtoLens.Encoding.Bytes.Parser Subscription
loop :: Subscription -> Bool -> Bool -> Parser Subscription
loop x :: Subscription
x required'subscription :: Bool
required'subscription required'topic :: Bool
required'topic
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do (let
missing :: [String]
missing
= (if Bool
required'subscription then
(:) "subscription"
else
[String] -> [String]
forall a. a -> a
Prelude.id)
((if Bool
required'topic then (:) "topic" else [String] -> [String]
forall a. a -> a
Prelude.id) [])
in
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [String]
missing then
() -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
missing :: [Prelude.String]))))
Subscription -> Parser Subscription
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter Subscription Subscription FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Subscription -> Subscription
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter Subscription Subscription FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) Subscription
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
10
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"topic"
Subscription -> Bool -> Bool -> Parser Subscription
loop
(Setter Subscription Subscription Text Text
-> Text -> Subscription -> Subscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Text
y Subscription
x)
Bool
required'subscription
Bool
Prelude.False
18
-> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
(Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
(case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
(Prelude.Left err :: UnicodeException
err)
-> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
(Prelude.Right r :: Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
"subscription"
Subscription -> Bool -> Bool -> Parser Subscription
loop
(Setter Subscription Subscription Text Text
-> Text -> Subscription -> Subscription
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription") Text
y Subscription
x)
Bool
Prelude.False
Bool
required'topic
wire :: Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
Subscription -> Bool -> Bool -> Parser Subscription
loop
(Setter Subscription Subscription FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Subscription -> Subscription
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
forall msg. Message msg => Lens' msg FieldSet
Setter Subscription Subscription FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Subscription
x)
Bool
required'subscription
Bool
required'topic
in
Parser Subscription -> String -> Parser Subscription
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Subscription -> Bool -> Bool -> Parser Subscription
loop Subscription
forall msg. Message msg => msg
Data.ProtoLens.defMessage Bool
Prelude.True Bool
Prelude.True)
"Subscription"
buildMessage :: Subscription -> Builder
buildMessage
= \ _x :: Subscription
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 10)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text Subscription Subscription Text Text
-> Subscription -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "topic" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"topic") Subscription
_x)))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt 18)
((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ bs :: ByteString
bs
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
(ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
Text -> ByteString
Data.Text.Encoding.encodeUtf8
(FoldLike Text Subscription Subscription Text Text
-> Subscription -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall s a (f :: * -> *).
(HasField s "subscription" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"subscription") Subscription
_x)))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet Subscription Subscription FieldSet FieldSet
-> Subscription -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet Subscription Subscription FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields Subscription
_x)))
instance Control.DeepSeq.NFData Subscription where
rnf :: Subscription -> ()
rnf
= \ x__ :: Subscription
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Subscription -> FieldSet
_Subscription'_unknownFields Subscription
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(Subscription -> Text
_Subscription'topic Subscription
x__)
(Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (Subscription -> Text
_Subscription'subscription Subscription
x__) ()))
data TxnAction
= COMMIT | ABORT
deriving stock (Int -> TxnAction -> ShowS
[TxnAction] -> ShowS
TxnAction -> String
(Int -> TxnAction -> ShowS)
-> (TxnAction -> String)
-> ([TxnAction] -> ShowS)
-> Show TxnAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxnAction] -> ShowS
$cshowList :: [TxnAction] -> ShowS
show :: TxnAction -> String
$cshow :: TxnAction -> String
showsPrec :: Int -> TxnAction -> ShowS
$cshowsPrec :: Int -> TxnAction -> ShowS
Prelude.Show, TxnAction -> TxnAction -> Bool
(TxnAction -> TxnAction -> Bool)
-> (TxnAction -> TxnAction -> Bool) -> Eq TxnAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxnAction -> TxnAction -> Bool
$c/= :: TxnAction -> TxnAction -> Bool
== :: TxnAction -> TxnAction -> Bool
$c== :: TxnAction -> TxnAction -> Bool
Prelude.Eq, Eq TxnAction
Eq TxnAction =>
(TxnAction -> TxnAction -> Ordering)
-> (TxnAction -> TxnAction -> Bool)
-> (TxnAction -> TxnAction -> Bool)
-> (TxnAction -> TxnAction -> Bool)
-> (TxnAction -> TxnAction -> Bool)
-> (TxnAction -> TxnAction -> TxnAction)
-> (TxnAction -> TxnAction -> TxnAction)
-> Ord TxnAction
TxnAction -> TxnAction -> Bool
TxnAction -> TxnAction -> Ordering
TxnAction -> TxnAction -> TxnAction
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxnAction -> TxnAction -> TxnAction
$cmin :: TxnAction -> TxnAction -> TxnAction
max :: TxnAction -> TxnAction -> TxnAction
$cmax :: TxnAction -> TxnAction -> TxnAction
>= :: TxnAction -> TxnAction -> Bool
$c>= :: TxnAction -> TxnAction -> Bool
> :: TxnAction -> TxnAction -> Bool
$c> :: TxnAction -> TxnAction -> Bool
<= :: TxnAction -> TxnAction -> Bool
$c<= :: TxnAction -> TxnAction -> Bool
< :: TxnAction -> TxnAction -> Bool
$c< :: TxnAction -> TxnAction -> Bool
compare :: TxnAction -> TxnAction -> Ordering
$ccompare :: TxnAction -> TxnAction -> Ordering
$cp1Ord :: Eq TxnAction
Prelude.Ord)
instance Data.ProtoLens.MessageEnum TxnAction where
maybeToEnum :: Int -> Maybe TxnAction
maybeToEnum 0 = TxnAction -> Maybe TxnAction
forall a. a -> Maybe a
Prelude.Just TxnAction
COMMIT
maybeToEnum 1 = TxnAction -> Maybe TxnAction
forall a. a -> Maybe a
Prelude.Just TxnAction
ABORT
maybeToEnum _ = Maybe TxnAction
forall a. Maybe a
Prelude.Nothing
showEnum :: TxnAction -> String
showEnum COMMIT = "COMMIT"
showEnum ABORT = "ABORT"
readEnum :: String -> Maybe TxnAction
readEnum k :: String
k
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "COMMIT" = TxnAction -> Maybe TxnAction
forall a. a -> Maybe a
Prelude.Just TxnAction
COMMIT
| String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k "ABORT" = TxnAction -> Maybe TxnAction
forall a. a -> Maybe a
Prelude.Just TxnAction
ABORT
| Bool
Prelude.otherwise
= Maybe Int -> (Int -> Maybe TxnAction) -> Maybe TxnAction
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe TxnAction
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded TxnAction where
minBound :: TxnAction
minBound = TxnAction
COMMIT
maxBound :: TxnAction
maxBound = TxnAction
ABORT
instance Prelude.Enum TxnAction where
toEnum :: Int -> TxnAction
toEnum k__ :: Int
k__
= TxnAction
-> (TxnAction -> TxnAction) -> Maybe TxnAction -> TxnAction
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
(String -> TxnAction
forall a. HasCallStack => String -> a
Prelude.error
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
"toEnum: unknown value for enum TxnAction: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
TxnAction -> TxnAction
forall a. a -> a
Prelude.id
(Int -> Maybe TxnAction
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
fromEnum :: TxnAction -> Int
fromEnum COMMIT = 0
fromEnum ABORT = 1
succ :: TxnAction -> TxnAction
succ ABORT
= String -> TxnAction
forall a. HasCallStack => String -> a
Prelude.error
"TxnAction.succ: bad argument ABORT. This value would be out of bounds."
succ COMMIT = TxnAction
ABORT
pred :: TxnAction -> TxnAction
pred COMMIT
= String -> TxnAction
forall a. HasCallStack => String -> a
Prelude.error
"TxnAction.pred: bad argument COMMIT. This value would be out of bounds."
pred ABORT = TxnAction
COMMIT
enumFrom :: TxnAction -> [TxnAction]
enumFrom = TxnAction -> [TxnAction]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
enumFromTo :: TxnAction -> TxnAction -> [TxnAction]
enumFromTo = TxnAction -> TxnAction -> [TxnAction]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
enumFromThen :: TxnAction -> TxnAction -> [TxnAction]
enumFromThen = TxnAction -> TxnAction -> [TxnAction]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
enumFromThenTo :: TxnAction -> TxnAction -> TxnAction -> [TxnAction]
enumFromThenTo = TxnAction -> TxnAction -> TxnAction -> [TxnAction]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault TxnAction where
fieldDefault :: TxnAction
fieldDefault = TxnAction
COMMIT
instance Control.DeepSeq.NFData TxnAction where
rnf :: TxnAction -> ()
rnf x__ :: TxnAction
x__ = TxnAction -> () -> ()
forall a b. a -> b -> b
Prelude.seq TxnAction
x__ ()
packedFileDescriptor :: Data.ByteString.ByteString
packedFileDescriptor :: ByteString
packedFileDescriptor
= "\n\
\\DLEpulsar_api.proto\DC2\fpulsar.proto\"\226\STX\n\
\\ACKSchema\DC2\DC2\n\
\\EOTname\CAN\SOH \STX(\tR\EOTname\DC2\US\n\
\\vschema_data\CAN\ETX \STX(\fR\n\
\schemaData\DC2-\n\
\\EOTtype\CAN\EOT \STX(\SO2\EM.pulsar.proto.Schema.TypeR\EOTtype\DC26\n\
\\n\
\properties\CAN\ENQ \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\"\187\SOH\n\
\\EOTType\DC2\b\n\
\\EOTNone\DLE\NUL\DC2\n\
\\n\
\\ACKString\DLE\SOH\DC2\b\n\
\\EOTJson\DLE\STX\DC2\f\n\
\\bProtobuf\DLE\ETX\DC2\b\n\
\\EOTAvro\DLE\EOT\DC2\b\n\
\\EOTBool\DLE\ENQ\DC2\b\n\
\\EOTInt8\DLE\ACK\DC2\t\n\
\\ENQInt16\DLE\a\DC2\t\n\
\\ENQInt32\DLE\b\DC2\t\n\
\\ENQInt64\DLE\t\DC2\t\n\
\\ENQFloat\DLE\n\
\\DC2\n\
\\n\
\\ACKDouble\DLE\v\DC2\b\n\
\\EOTDate\DLE\f\DC2\b\n\
\\EOTTime\DLE\r\DC2\r\n\
\\tTimestamp\DLE\SO\DC2\f\n\
\\bKeyValue\DLE\SI\"\165\SOH\n\
\\rMessageIdData\DC2\SUB\n\
\\bledgerId\CAN\SOH \STX(\EOTR\bledgerId\DC2\CAN\n\
\\aentryId\CAN\STX \STX(\EOTR\aentryId\DC2 \n\
\\tpartition\CAN\ETX \SOH(\ENQ:\STX-1R\tpartition\DC2#\n\
\\vbatch_index\CAN\EOT \SOH(\ENQ:\STX-1R\n\
\batchIndex\DC2\ETB\n\
\\aack_set\CAN\ENQ \ETX(\ETXR\ACKackSet\"2\n\
\\bKeyValue\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\tR\ENQvalue\"6\n\
\\fKeyLongValue\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\EOTR\ENQvalue\"2\n\
\\bIntRange\DC2\DC4\n\
\\ENQstart\CAN\SOH \STX(\ENQR\ENQstart\DC2\DLE\n\
\\ETXend\CAN\STX \STX(\ENQR\ETXend\"l\n\
\\SOEncryptionKeys\DC2\DLE\n\
\\ETXkey\CAN\SOH \STX(\tR\ETXkey\DC2\DC4\n\
\\ENQvalue\CAN\STX \STX(\fR\ENQvalue\DC22\n\
\\bmetadata\CAN\ETX \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata\"\209\t\n\
\\SIMessageMetadata\DC2#\n\
\\rproducer_name\CAN\SOH \STX(\tR\fproducerName\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2!\n\
\\fpublish_time\CAN\ETX \STX(\EOTR\vpublishTime\DC26\n\
\\n\
\properties\CAN\EOT \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\DC2'\n\
\\SIreplicated_from\CAN\ENQ \SOH(\tR\SOreplicatedFrom\DC2#\n\
\\rpartition_key\CAN\ACK \SOH(\tR\fpartitionKey\DC2!\n\
\\freplicate_to\CAN\a \ETX(\tR\vreplicateTo\DC2E\n\
\\vcompression\CAN\b \SOH(\SO2\GS.pulsar.proto.CompressionType:\EOTNONER\vcompression\DC2.\n\
\\DC1uncompressed_size\CAN\t \SOH(\r:\SOH0R\DLEuncompressedSize\DC24\n\
\\NAKnum_messages_in_batch\CAN\v \SOH(\ENQ:\SOH1R\DC2numMessagesInBatch\DC2 \n\
\\n\
\event_time\CAN\f \SOH(\EOT:\SOH0R\teventTime\DC2E\n\
\\SIencryption_keys\CAN\r \ETX(\v2\FS.pulsar.proto.EncryptionKeysR\SOencryptionKeys\DC2'\n\
\\SIencryption_algo\CAN\SO \SOH(\tR\SOencryptionAlgo\DC2)\n\
\\DLEencryption_param\CAN\SI \SOH(\fR\SIencryptionParam\DC2%\n\
\\SOschema_version\CAN\DLE \SOH(\fR\rschemaVersion\DC2@\n\
\\EMpartition_key_b64_encoded\CAN\DC1 \SOH(\b:\ENQfalseR\SYNpartitionKeyB64Encoded\DC2!\n\
\\fordering_key\CAN\DC2 \SOH(\fR\vorderingKey\DC2&\n\
\\SIdeliver_at_time\CAN\DC3 \SOH(\ETXR\rdeliverAtTime\DC2\US\n\
\\vmarker_type\CAN\DC4 \SOH(\ENQR\n\
\markerType\DC2(\n\
\\DLEtxnid_least_bits\CAN\SYN \SOH(\EOTR\SOtxnidLeastBits\DC2&\n\
\\SItxnid_most_bits\CAN\ETB \SOH(\EOTR\rtxnidMostBits\DC21\n\
\\DC3highest_sequence_id\CAN\CAN \SOH(\EOT:\SOH0R\DC1highestSequenceId\DC2$\n\
\\n\
\null_value\CAN\EM \SOH(\b:\ENQfalseR\tnullValue\DC2\DC2\n\
\\EOTuuid\CAN\SUB \SOH(\tR\EOTuuid\DC2-\n\
\\DC3num_chunks_from_msg\CAN\ESC \SOH(\ENQR\DLEnumChunksFromMsg\DC2/\n\
\\DC4total_chunk_msg_size\CAN\FS \SOH(\ENQR\DC1totalChunkMsgSize\DC2\EM\n\
\\bchunk_id\CAN\GS \SOH(\ENQR\achunkId\DC23\n\
\\DC2null_partition_key\CAN\RS \SOH(\b:\ENQfalseR\DLEnullPartitionKey\"\198\ETX\n\
\\NAKSingleMessageMetadata\DC26\n\
\\n\
\properties\CAN\SOH \ETX(\v2\SYN.pulsar.proto.KeyValueR\n\
\properties\DC2#\n\
\\rpartition_key\CAN\STX \SOH(\tR\fpartitionKey\DC2!\n\
\\fpayload_size\CAN\ETX \STX(\ENQR\vpayloadSize\DC2*\n\
\\rcompacted_out\CAN\EOT \SOH(\b:\ENQfalseR\fcompactedOut\DC2 \n\
\\n\
\event_time\CAN\ENQ \SOH(\EOT:\SOH0R\teventTime\DC2@\n\
\\EMpartition_key_b64_encoded\CAN\ACK \SOH(\b:\ENQfalseR\SYNpartitionKeyB64Encoded\DC2!\n\
\\fordering_key\CAN\a \SOH(\fR\vorderingKey\DC2\US\n\
\\vsequence_id\CAN\b \SOH(\EOTR\n\
\sequenceId\DC2$\n\
\\n\
\null_value\CAN\t \SOH(\b:\ENQfalseR\tnullValue\DC23\n\
\\DC2null_partition_key\CAN\n\
\ \SOH(\b:\ENQfalseR\DLEnullPartitionKey\"\230\ETX\n\
\\SOCommandConnect\DC2%\n\
\\SOclient_version\CAN\SOH \STX(\tR\rclientVersion\DC29\n\
\\vauth_method\CAN\STX \SOH(\SO2\CAN.pulsar.proto.AuthMethodR\n\
\authMethod\DC2(\n\
\\DLEauth_method_name\CAN\ENQ \SOH(\tR\SOauthMethodName\DC2\ESC\n\
\\tauth_data\CAN\ETX \SOH(\fR\bauthData\DC2,\n\
\\DLEprotocol_version\CAN\EOT \SOH(\ENQ:\SOH0R\SIprotocolVersion\DC2-\n\
\\DC3proxy_to_broker_url\CAN\ACK \SOH(\tR\DLEproxyToBrokerUrl\DC2-\n\
\\DC2original_principal\CAN\a \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\b \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\t \SOH(\tR\DC2originalAuthMethod\DC2?\n\
\\rfeature_flags\CAN\n\
\ \SOH(\v2\SUB.pulsar.proto.FeatureFlagsR\ffeatureFlags\"I\n\
\\fFeatureFlags\DC29\n\
\\NAKsupports_auth_refresh\CAN\SOH \SOH(\b:\ENQfalseR\DC3supportsAuthRefresh\"\145\SOH\n\
\\DLECommandConnected\DC2%\n\
\\SOserver_version\CAN\SOH \STX(\tR\rserverVersion\DC2,\n\
\\DLEprotocol_version\CAN\STX \SOH(\ENQ:\SOH0R\SIprotocolVersion\DC2(\n\
\\DLEmax_message_size\CAN\ETX \SOH(\ENQR\SOmaxMessageSize\"\158\SOH\n\
\\DC3CommandAuthResponse\DC2%\n\
\\SOclient_version\CAN\SOH \SOH(\tR\rclientVersion\DC22\n\
\\bresponse\CAN\STX \SOH(\v2\SYN.pulsar.proto.AuthDataR\bresponse\DC2,\n\
\\DLEprotocol_version\CAN\ETX \SOH(\ENQ:\SOH0R\SIprotocolVersion\"\161\SOH\n\
\\DC4CommandAuthChallenge\DC2%\n\
\\SOserver_version\CAN\SOH \SOH(\tR\rserverVersion\DC24\n\
\\tchallenge\CAN\STX \SOH(\v2\SYN.pulsar.proto.AuthDataR\tchallenge\DC2,\n\
\\DLEprotocol_version\CAN\ETX \SOH(\ENQ:\SOH0R\SIprotocolVersion\"Q\n\
\\bAuthData\DC2(\n\
\\DLEauth_method_name\CAN\SOH \SOH(\tR\SOauthMethodName\DC2\ESC\n\
\\tauth_data\CAN\STX \SOH(\fR\bauthData\"\203\SOH\n\
\\rKeySharedMeta\DC2A\n\
\\rkeySharedMode\CAN\SOH \STX(\SO2\ESC.pulsar.proto.KeySharedModeR\rkeySharedMode\DC26\n\
\\n\
\hashRanges\CAN\ETX \ETX(\v2\SYN.pulsar.proto.IntRangeR\n\
\hashRanges\DC2?\n\
\\ETBallowOutOfOrderDelivery\CAN\EOT \SOH(\b:\ENQfalseR\ETBallowOutOfOrderDelivery\"\235\a\n\
\\DLECommandSubscribe\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\"\n\
\\fsubscription\CAN\STX \STX(\tR\fsubscription\DC2@\n\
\\asubType\CAN\ETX \STX(\SO2&.pulsar.proto.CommandSubscribe.SubTypeR\asubType\DC2\US\n\
\\vconsumer_id\CAN\EOT \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\ENQ \STX(\EOTR\trequestId\DC2#\n\
\\rconsumer_name\CAN\ACK \SOH(\tR\fconsumerName\DC2%\n\
\\SOpriority_level\CAN\a \SOH(\ENQR\rpriorityLevel\DC2\RS\n\
\\adurable\CAN\b \SOH(\b:\EOTtrueR\adurable\DC2E\n\
\\DLEstart_message_id\CAN\t \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\SOstartMessageId\DC22\n\
\\bmetadata\CAN\n\
\ \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata\DC2%\n\
\\SOread_compacted\CAN\v \SOH(\bR\rreadCompacted\DC2,\n\
\\ACKschema\CAN\f \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2`\n\
\\SIinitialPosition\CAN\r \SOH(\SO2..pulsar.proto.CommandSubscribe.InitialPosition:\ACKLatestR\SIinitialPosition\DC2@\n\
\\FSreplicate_subscription_state\CAN\SO \SOH(\bR\SUBreplicateSubscriptionState\DC26\n\
\\DC4force_topic_creation\CAN\SI \SOH(\b:\EOTtrueR\DC2forceTopicCreation\DC2O\n\
\#start_message_rollback_duration_sec\CAN\DLE \SOH(\EOT:\SOH0R\USstartMessageRollbackDurationSec\DC2A\n\
\\rkeySharedMeta\CAN\DC1 \SOH(\v2\ESC.pulsar.proto.KeySharedMetaR\rkeySharedMeta\"B\n\
\\aSubType\DC2\r\n\
\\tExclusive\DLE\NUL\DC2\n\
\\n\
\\ACKShared\DLE\SOH\DC2\f\n\
\\bFailover\DLE\STX\DC2\SO\n\
\\n\
\Key_Shared\DLE\ETX\"+\n\
\\SIInitialPosition\DC2\n\
\\n\
\\ACKLatest\DLE\NUL\DC2\f\n\
\\bEarliest\DLE\SOH\"\229\SOH\n\
\\USCommandPartitionedTopicMetadata\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2-\n\
\\DC2original_principal\CAN\ETX \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\EOT \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\ENQ \SOH(\tR\DC2originalAuthMethod\"\184\STX\n\
\'CommandPartitionedTopicMetadataResponse\DC2\RS\n\
\\n\
\partitions\CAN\SOH \SOH(\rR\n\
\partitions\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2\\\n\
\\bresponse\CAN\ETX \SOH(\SO2@.pulsar.proto.CommandPartitionedTopicMetadataResponse.LookupTypeR\bresponse\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"%\n\
\\n\
\LookupType\DC2\v\n\
\\aSuccess\DLE\NUL\DC2\n\
\\n\
\\ACKFailed\DLE\SOH\"\191\STX\n\
\\DC2CommandLookupTopic\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2+\n\
\\rauthoritative\CAN\ETX \SOH(\b:\ENQfalseR\rauthoritative\DC2-\n\
\\DC2original_principal\CAN\EOT \SOH(\tR\DC1originalPrincipal\DC2,\n\
\\DC2original_auth_data\CAN\ENQ \SOH(\tR\DLEoriginalAuthData\DC20\n\
\\DC4original_auth_method\CAN\ACK \SOH(\tR\DC2originalAuthMethod\DC28\n\
\\CANadvertised_listener_name\CAN\a \SOH(\tR\SYNadvertisedListenerName\"\217\ETX\n\
\\SUBCommandLookupTopicResponse\DC2*\n\
\\DLEbrokerServiceUrl\CAN\SOH \SOH(\tR\DLEbrokerServiceUrl\DC20\n\
\\DC3brokerServiceUrlTls\CAN\STX \SOH(\tR\DC3brokerServiceUrlTls\DC2O\n\
\\bresponse\CAN\ETX \SOH(\SO23.pulsar.proto.CommandLookupTopicResponse.LookupTypeR\bresponse\DC2\GS\n\
\\n\
\request_id\CAN\EOT \STX(\EOTR\trequestId\DC2+\n\
\\rauthoritative\CAN\ENQ \SOH(\b:\ENQfalseR\rauthoritative\DC2/\n\
\\ENQerror\CAN\ACK \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\a \SOH(\tR\amessage\DC2@\n\
\\EMproxy_through_service_url\CAN\b \SOH(\b:\ENQfalseR\SYNproxyThroughServiceUrl\"3\n\
\\n\
\LookupType\DC2\f\n\
\\bRedirect\DLE\NUL\DC2\v\n\
\\aConnect\DLE\SOH\DC2\n\
\\n\
\\ACKFailed\DLE\STX\"\241\STX\n\
\\SICommandProducer\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\US\n\
\\vproducer_id\CAN\STX \STX(\EOTR\n\
\producerId\DC2\GS\n\
\\n\
\request_id\CAN\ETX \STX(\EOTR\trequestId\DC2#\n\
\\rproducer_name\CAN\EOT \SOH(\tR\fproducerName\DC2#\n\
\\tencrypted\CAN\ENQ \SOH(\b:\ENQfalseR\tencrypted\DC22\n\
\\bmetadata\CAN\ACK \ETX(\v2\SYN.pulsar.proto.KeyValueR\bmetadata\DC2,\n\
\\ACKschema\CAN\a \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2\ETB\n\
\\ENQepoch\CAN\b \SOH(\EOT:\SOH0R\ENQepoch\DC2C\n\
\\ESCuser_provided_producer_name\CAN\t \SOH(\b:\EOTtrueR\CANuserProvidedProducerName\"\162\STX\n\
\\vCommandSend\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2$\n\
\\fnum_messages\CAN\ETX \SOH(\ENQ:\SOH1R\vnumMessages\DC2+\n\
\\DLEtxnid_least_bits\CAN\EOT \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ENQ \SOH(\EOT:\SOH0R\rtxnidMostBits\DC21\n\
\\DC3highest_sequence_id\CAN\ACK \SOH(\EOT:\SOH0R\DC1highestSequenceId\DC2 \n\
\\bis_chunk\CAN\a \SOH(\b:\ENQfalseR\aisChunk\"\197\SOH\n\
\\DC2CommandSendReceipt\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2:\n\
\\n\
\message_id\CAN\ETX \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC21\n\
\\DC3highest_sequence_id\CAN\EOT \SOH(\EOT:\SOH0R\DC1highestSequenceId\"\159\SOH\n\
\\DLECommandSendError\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\US\n\
\\vsequence_id\CAN\STX \STX(\EOTR\n\
\sequenceId\DC2/\n\
\\ENQerror\CAN\ETX \STX(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\EOT \STX(\tR\amessage\"\180\SOH\n\
\\SOCommandMessage\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2:\n\
\\n\
\message_id\CAN\STX \STX(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC2,\n\
\\DLEredelivery_count\CAN\ETX \SOH(\r:\SOH0R\SIredeliveryCount\DC2\ETB\n\
\\aack_set\CAN\EOT \ETX(\ETXR\ACKackSet\"\204\EOT\n\
\\n\
\CommandAck\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2;\n\
\\back_type\CAN\STX \STX(\SO2 .pulsar.proto.CommandAck.AckTypeR\aackType\DC2:\n\
\\n\
\message_id\CAN\ETX \ETX(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC2S\n\
\\DLEvalidation_error\CAN\EOT \SOH(\SO2(.pulsar.proto.CommandAck.ValidationErrorR\SIvalidationError\DC2:\n\
\\n\
\properties\CAN\ENQ \ETX(\v2\SUB.pulsar.proto.KeyLongValueR\n\
\properties\DC2+\n\
\\DLEtxnid_least_bits\CAN\ACK \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\a \SOH(\EOT:\SOH0R\rtxnidMostBits\")\n\
\\aAckType\DC2\SO\n\
\\n\
\Individual\DLE\NUL\DC2\SO\n\
\\n\
\Cumulative\DLE\SOH\"\143\SOH\n\
\\SIValidationError\DC2\RS\n\
\\SUBUncompressedSizeCorruption\DLE\NUL\DC2\SYN\n\
\\DC2DecompressionError\DLE\SOH\DC2\DC4\n\
\\DLEChecksumMismatch\DLE\STX\DC2\EM\n\
\\NAKBatchDeSerializeError\DLE\ETX\DC2\DC3\n\
\\SIDecryptionError\DLE\EOT\"\216\SOH\n\
\\DC2CommandAckResponse\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"b\n\
\\ESCCommandActiveConsumerChange\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\"\n\
\\tis_active\CAN\STX \SOH(\b:\ENQfalseR\bisActive\"V\n\
\\vCommandFlow\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2&\n\
\\SOmessagePermits\CAN\STX \STX(\rR\SOmessagePermits\"T\n\
\\DC2CommandUnsubscribe\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\"\187\SOH\n\
\\vCommandSeek\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\DC2:\n\
\\n\
\message_id\CAN\ETX \SOH(\v2\ESC.pulsar.proto.MessageIdDataR\tmessageId\DC20\n\
\\DC4message_publish_time\CAN\EOT \SOH(\EOTR\DC2messagePublishTime\";\n\
\\CANCommandReachedEndOfTopic\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\"V\n\
\\DC4CommandCloseProducer\DC2\US\n\
\\vproducer_id\CAN\SOH \STX(\EOTR\n\
\producerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\"V\n\
\\DC4CommandCloseConsumer\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\"\135\SOH\n\
\&CommandRedeliverUnacknowledgedMessages\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2<\n\
\\vmessage_ids\CAN\STX \ETX(\v2\ESC.pulsar.proto.MessageIdDataR\n\
\messageIds\"]\n\
\\SOCommandSuccess\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2,\n\
\\ACKschema\CAN\STX \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\"\177\SOH\n\
\\SYNCommandProducerSuccess\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2#\n\
\\rproducer_name\CAN\STX \STX(\tR\fproducerName\DC2,\n\
\\DLElast_sequence_id\CAN\ETX \SOH(\ETX:\STX-1R\SOlastSequenceId\DC2%\n\
\\SOschema_version\CAN\EOT \SOH(\fR\rschemaVersion\"x\n\
\\fCommandError\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2/\n\
\\ENQerror\CAN\STX \STX(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ETX \STX(\tR\amessage\"\r\n\
\\vCommandPing\"\r\n\
\\vCommandPong\"V\n\
\\DC4CommandConsumerStats\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\US\n\
\\vconsumer_id\CAN\EOT \STX(\EOTR\n\
\consumerId\"\240\EOT\n\
\\FSCommandConsumerStatsResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2\RS\n\
\\n\
\msgRateOut\CAN\EOT \SOH(\SOHR\n\
\msgRateOut\DC2*\n\
\\DLEmsgThroughputOut\CAN\ENQ \SOH(\SOHR\DLEmsgThroughputOut\DC2*\n\
\\DLEmsgRateRedeliver\CAN\ACK \SOH(\SOHR\DLEmsgRateRedeliver\DC2\"\n\
\\fconsumerName\CAN\a \SOH(\tR\fconsumerName\DC2*\n\
\\DLEavailablePermits\CAN\b \SOH(\EOTR\DLEavailablePermits\DC2(\n\
\\SIunackedMessages\CAN\t \SOH(\EOTR\SIunackedMessages\DC2B\n\
\\FSblockedConsumerOnUnackedMsgs\CAN\n\
\ \SOH(\bR\FSblockedConsumerOnUnackedMsgs\DC2\CAN\n\
\\aaddress\CAN\v \SOH(\tR\aaddress\DC2&\n\
\\SOconnectedSince\CAN\f \SOH(\tR\SOconnectedSince\DC2\DC2\n\
\\EOTtype\CAN\r \SOH(\tR\EOTtype\DC2&\n\
\\SOmsgRateExpired\CAN\SO \SOH(\SOHR\SOmsgRateExpired\DC2\RS\n\
\\n\
\msgBacklog\CAN\SI \SOH(\EOTR\n\
\msgBacklog\"Y\n\
\\ETBCommandGetLastMessageId\DC2\US\n\
\\vconsumer_id\CAN\SOH \STX(\EOTR\n\
\consumerId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\"\133\SOH\n\
\\USCommandGetLastMessageIdResponse\DC2C\n\
\\SIlast_message_id\CAN\SOH \STX(\v2\ESC.pulsar.proto.MessageIdDataR\rlastMessageId\DC2\GS\n\
\\n\
\request_id\CAN\STX \STX(\EOTR\trequestId\"\223\SOH\n\
\\ESCCommandGetTopicsOfNamespace\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\FS\n\
\\tnamespace\CAN\STX \STX(\tR\tnamespace\DC2N\n\
\\EOTmode\CAN\ETX \SOH(\SO2..pulsar.proto.CommandGetTopicsOfNamespace.Mode:\n\
\PERSISTENTR\EOTmode\"3\n\
\\EOTMode\DC2\SO\n\
\\n\
\PERSISTENT\DLE\NUL\DC2\DC2\n\
\\SONON_PERSISTENT\DLE\SOH\DC2\a\n\
\\ETXALL\DLE\STX\"\\\n\
\#CommandGetTopicsOfNamespaceResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\SYN\n\
\\ACKtopics\CAN\STX \ETX(\tR\ACKtopics\"n\n\
\\DLECommandGetSchema\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\DC4\n\
\\ENQtopic\CAN\STX \STX(\tR\ENQtopic\DC2%\n\
\\SOschema_version\CAN\ETX \SOH(\fR\rschemaVersion\"\237\SOH\n\
\\CANCommandGetSchemaResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2,\n\
\\ACKschema\CAN\EOT \SOH(\v2\DC4.pulsar.proto.SchemaR\ACKschema\DC2%\n\
\\SOschema_version\CAN\ENQ \SOH(\fR\rschemaVersion\"}\n\
\\CANCommandGetOrCreateSchema\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2\DC4\n\
\\ENQtopic\CAN\STX \STX(\tR\ENQtopic\DC2,\n\
\\ACKschema\CAN\ETX \STX(\v2\DC4.pulsar.proto.SchemaR\ACKschema\"\199\SOH\n\
\ CommandGetOrCreateSchemaResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC28\n\
\\n\
\error_code\CAN\STX \SOH(\SO2\EM.pulsar.proto.ServerErrorR\terrorCode\DC2#\n\
\\rerror_message\CAN\ETX \SOH(\tR\ferrorMessage\DC2%\n\
\\SOschema_version\CAN\EOT \SOH(\fR\rschemaVersion\"q\n\
\\rCommandNewTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2)\n\
\\SItxn_ttl_seconds\CAN\STX \SOH(\EOT:\SOH0R\rtxnTtlSeconds\DC2\SYN\n\
\\ENQtc_id\CAN\ETX \SOH(\EOT:\SOH0R\EOTtcId\"\217\SOH\n\
\\NAKCommandNewTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"\177\SOH\n\
\\CANCommandAddPartitionToTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2\RS\n\
\\n\
\partitions\CAN\EOT \ETX(\tR\n\
\partitions\"\228\SOH\n\
\ CommandAddPartitionToTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"H\n\
\\fSubscription\DC2\DC4\n\
\\ENQtopic\CAN\SOH \STX(\tR\ENQtopic\DC2\"\n\
\\fsubscription\CAN\STX \STX(\tR\fsubscription\"\212\SOH\n\
\\ESCCommandAddSubscriptionToTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2>\n\
\\fsubscription\CAN\EOT \ETX(\v2\SUB.pulsar.proto.SubscriptionR\fsubscription\"\231\SOH\n\
\#CommandAddSubscriptionToTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"\190\SOH\n\
\\rCommandEndTxn\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC26\n\
\\n\
\txn_action\CAN\EOT \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction\"\217\SOH\n\
\\NAKCommandEndTxnResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"\223\SOH\n\
\\CANCommandEndTxnOnPartition\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2\DC4\n\
\\ENQtopic\CAN\EOT \SOH(\tR\ENQtopic\DC26\n\
\\n\
\txn_action\CAN\ENQ \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction\"\228\SOH\n\
\ CommandEndTxnOnPartitionResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"\140\STX\n\
\\ESCCommandEndTxnOnSubscription\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2>\n\
\\fsubscription\CAN\EOT \SOH(\v2\SUB.pulsar.proto.SubscriptionR\fsubscription\DC26\n\
\\n\
\txn_action\CAN\ENQ \SOH(\SO2\ETB.pulsar.proto.TxnActionR\ttxnAction\"\231\SOH\n\
\#CommandEndTxnOnSubscriptionResponse\DC2\GS\n\
\\n\
\request_id\CAN\SOH \STX(\EOTR\trequestId\DC2+\n\
\\DLEtxnid_least_bits\CAN\STX \SOH(\EOT:\SOH0R\SOtxnidLeastBits\DC2)\n\
\\SItxnid_most_bits\CAN\ETX \SOH(\EOT:\SOH0R\rtxnidMostBits\DC2/\n\
\\ENQerror\CAN\EOT \SOH(\SO2\EM.pulsar.proto.ServerErrorR\ENQerror\DC2\CAN\n\
\\amessage\CAN\ENQ \SOH(\tR\amessage\"\200(\n\
\\vBaseCommand\DC22\n\
\\EOTtype\CAN\SOH \STX(\SO2\RS.pulsar.proto.BaseCommand.TypeR\EOTtype\DC26\n\
\\aconnect\CAN\STX \SOH(\v2\FS.pulsar.proto.CommandConnectR\aconnect\DC2<\n\
\\tconnected\CAN\ETX \SOH(\v2\RS.pulsar.proto.CommandConnectedR\tconnected\DC2<\n\
\\tsubscribe\CAN\EOT \SOH(\v2\RS.pulsar.proto.CommandSubscribeR\tsubscribe\DC29\n\
\\bproducer\CAN\ENQ \SOH(\v2\GS.pulsar.proto.CommandProducerR\bproducer\DC2-\n\
\\EOTsend\CAN\ACK \SOH(\v2\EM.pulsar.proto.CommandSendR\EOTsend\DC2C\n\
\\fsend_receipt\CAN\a \SOH(\v2 .pulsar.proto.CommandSendReceiptR\vsendReceipt\DC2=\n\
\\n\
\send_error\CAN\b \SOH(\v2\RS.pulsar.proto.CommandSendErrorR\tsendError\DC26\n\
\\amessage\CAN\t \SOH(\v2\FS.pulsar.proto.CommandMessageR\amessage\DC2*\n\
\\ETXack\CAN\n\
\ \SOH(\v2\CAN.pulsar.proto.CommandAckR\ETXack\DC2-\n\
\\EOTflow\CAN\v \SOH(\v2\EM.pulsar.proto.CommandFlowR\EOTflow\DC2B\n\
\\vunsubscribe\CAN\f \SOH(\v2 .pulsar.proto.CommandUnsubscribeR\vunsubscribe\DC26\n\
\\asuccess\CAN\r \SOH(\v2\FS.pulsar.proto.CommandSuccessR\asuccess\DC20\n\
\\ENQerror\CAN\SO \SOH(\v2\SUB.pulsar.proto.CommandErrorR\ENQerror\DC2I\n\
\\SOclose_producer\CAN\SI \SOH(\v2\".pulsar.proto.CommandCloseProducerR\rcloseProducer\DC2I\n\
\\SOclose_consumer\CAN\DLE \SOH(\v2\".pulsar.proto.CommandCloseConsumerR\rcloseConsumer\DC2O\n\
\\DLEproducer_success\CAN\DC1 \SOH(\v2$.pulsar.proto.CommandProducerSuccessR\SIproducerSuccess\DC2-\n\
\\EOTping\CAN\DC2 \SOH(\v2\EM.pulsar.proto.CommandPingR\EOTping\DC2-\n\
\\EOTpong\CAN\DC3 \SOH(\v2\EM.pulsar.proto.CommandPongR\EOTpong\DC2~\n\
\\USredeliverUnacknowledgedMessages\CAN\DC4 \SOH(\v24.pulsar.proto.CommandRedeliverUnacknowledgedMessagesR\USredeliverUnacknowledgedMessages\DC2[\n\
\\DC1partitionMetadata\CAN\NAK \SOH(\v2-.pulsar.proto.CommandPartitionedTopicMetadataR\DC1partitionMetadata\DC2s\n\
\\EMpartitionMetadataResponse\CAN\SYN \SOH(\v25.pulsar.proto.CommandPartitionedTopicMetadataResponseR\EMpartitionMetadataResponse\DC2B\n\
\\vlookupTopic\CAN\ETB \SOH(\v2 .pulsar.proto.CommandLookupTopicR\vlookupTopic\DC2Z\n\
\\DC3lookupTopicResponse\CAN\CAN \SOH(\v2(.pulsar.proto.CommandLookupTopicResponseR\DC3lookupTopicResponse\DC2H\n\
\\rconsumerStats\CAN\EM \SOH(\v2\".pulsar.proto.CommandConsumerStatsR\rconsumerStats\DC2`\n\
\\NAKconsumerStatsResponse\CAN\SUB \SOH(\v2*.pulsar.proto.CommandConsumerStatsResponseR\NAKconsumerStatsResponse\DC2T\n\
\\DC1reachedEndOfTopic\CAN\ESC \SOH(\v2&.pulsar.proto.CommandReachedEndOfTopicR\DC1reachedEndOfTopic\DC2-\n\
\\EOTseek\CAN\FS \SOH(\v2\EM.pulsar.proto.CommandSeekR\EOTseek\DC2Q\n\
\\DLEgetLastMessageId\CAN\GS \SOH(\v2%.pulsar.proto.CommandGetLastMessageIdR\DLEgetLastMessageId\DC2i\n\
\\CANgetLastMessageIdResponse\CAN\RS \SOH(\v2-.pulsar.proto.CommandGetLastMessageIdResponseR\CANgetLastMessageIdResponse\DC2_\n\
\\SYNactive_consumer_change\CAN\US \SOH(\v2).pulsar.proto.CommandActiveConsumerChangeR\DC4activeConsumerChange\DC2]\n\
\\DC4getTopicsOfNamespace\CAN \SOH(\v2).pulsar.proto.CommandGetTopicsOfNamespaceR\DC4getTopicsOfNamespace\DC2u\n\
\\FSgetTopicsOfNamespaceResponse\CAN! \SOH(\v21.pulsar.proto.CommandGetTopicsOfNamespaceResponseR\FSgetTopicsOfNamespaceResponse\DC2<\n\
\\tgetSchema\CAN\" \SOH(\v2\RS.pulsar.proto.CommandGetSchemaR\tgetSchema\DC2T\n\
\\DC1getSchemaResponse\CAN# \SOH(\v2&.pulsar.proto.CommandGetSchemaResponseR\DC1getSchemaResponse\DC2H\n\
\\rauthChallenge\CAN$ \SOH(\v2\".pulsar.proto.CommandAuthChallengeR\rauthChallenge\DC2E\n\
\\fauthResponse\CAN% \SOH(\v2!.pulsar.proto.CommandAuthResponseR\fauthResponse\DC2B\n\
\\vackResponse\CAN& \SOH(\v2 .pulsar.proto.CommandAckResponseR\vackResponse\DC2T\n\
\\DC1getOrCreateSchema\CAN' \SOH(\v2&.pulsar.proto.CommandGetOrCreateSchemaR\DC1getOrCreateSchema\DC2l\n\
\\EMgetOrCreateSchemaResponse\CAN( \SOH(\v2..pulsar.proto.CommandGetOrCreateSchemaResponseR\EMgetOrCreateSchemaResponse\DC23\n\
\\ACKnewTxn\CAN2 \SOH(\v2\ESC.pulsar.proto.CommandNewTxnR\ACKnewTxn\DC2K\n\
\\SOnewTxnResponse\CAN3 \SOH(\v2#.pulsar.proto.CommandNewTxnResponseR\SOnewTxnResponse\DC2T\n\
\\DC1addPartitionToTxn\CAN4 \SOH(\v2&.pulsar.proto.CommandAddPartitionToTxnR\DC1addPartitionToTxn\DC2l\n\
\\EMaddPartitionToTxnResponse\CAN5 \SOH(\v2..pulsar.proto.CommandAddPartitionToTxnResponseR\EMaddPartitionToTxnResponse\DC2]\n\
\\DC4addSubscriptionToTxn\CAN6 \SOH(\v2).pulsar.proto.CommandAddSubscriptionToTxnR\DC4addSubscriptionToTxn\DC2u\n\
\\FSaddSubscriptionToTxnResponse\CAN7 \SOH(\v21.pulsar.proto.CommandAddSubscriptionToTxnResponseR\FSaddSubscriptionToTxnResponse\DC23\n\
\\ACKendTxn\CAN8 \SOH(\v2\ESC.pulsar.proto.CommandEndTxnR\ACKendTxn\DC2K\n\
\\SOendTxnResponse\CAN9 \SOH(\v2#.pulsar.proto.CommandEndTxnResponseR\SOendTxnResponse\DC2T\n\
\\DC1endTxnOnPartition\CAN: \SOH(\v2&.pulsar.proto.CommandEndTxnOnPartitionR\DC1endTxnOnPartition\DC2l\n\
\\EMendTxnOnPartitionResponse\CAN; \SOH(\v2..pulsar.proto.CommandEndTxnOnPartitionResponseR\EMendTxnOnPartitionResponse\DC2]\n\
\\DC4endTxnOnSubscription\CAN< \SOH(\v2).pulsar.proto.CommandEndTxnOnSubscriptionR\DC4endTxnOnSubscription\DC2u\n\
\\FSendTxnOnSubscriptionResponse\CAN= \SOH(\v21.pulsar.proto.CommandEndTxnOnSubscriptionResponseR\FSendTxnOnSubscriptionResponse\"\223\b\n\
\\EOTType\DC2\v\n\
\\aCONNECT\DLE\STX\DC2\r\n\
\\tCONNECTED\DLE\ETX\DC2\r\n\
\\tSUBSCRIBE\DLE\EOT\DC2\f\n\
\\bPRODUCER\DLE\ENQ\DC2\b\n\
\\EOTSEND\DLE\ACK\DC2\DLE\n\
\\fSEND_RECEIPT\DLE\a\DC2\SO\n\
\\n\
\SEND_ERROR\DLE\b\DC2\v\n\
\\aMESSAGE\DLE\t\DC2\a\n\
\\ETXACK\DLE\n\
\\DC2\b\n\
\\EOTFLOW\DLE\v\DC2\SI\n\
\\vUNSUBSCRIBE\DLE\f\DC2\v\n\
\\aSUCCESS\DLE\r\DC2\t\n\
\\ENQERROR\DLE\SO\DC2\DC2\n\
\\SOCLOSE_PRODUCER\DLE\SI\DC2\DC2\n\
\\SOCLOSE_CONSUMER\DLE\DLE\DC2\DC4\n\
\\DLEPRODUCER_SUCCESS\DLE\DC1\DC2\b\n\
\\EOTPING\DLE\DC2\DC2\b\n\
\\EOTPONG\DLE\DC3\DC2%\n\
\!REDELIVER_UNACKNOWLEDGED_MESSAGES\DLE\DC4\DC2\CAN\n\
\\DC4PARTITIONED_METADATA\DLE\NAK\DC2!\n\
\\GSPARTITIONED_METADATA_RESPONSE\DLE\SYN\DC2\n\
\\n\
\\ACKLOOKUP\DLE\ETB\DC2\DC3\n\
\\SILOOKUP_RESPONSE\DLE\CAN\DC2\DC2\n\
\\SOCONSUMER_STATS\DLE\EM\DC2\ESC\n\
\\ETBCONSUMER_STATS_RESPONSE\DLE\SUB\DC2\CAN\n\
\\DC4REACHED_END_OF_TOPIC\DLE\ESC\DC2\b\n\
\\EOTSEEK\DLE\FS\DC2\ETB\n\
\\DC3GET_LAST_MESSAGE_ID\DLE\GS\DC2 \n\
\\FSGET_LAST_MESSAGE_ID_RESPONSE\DLE\RS\DC2\SUB\n\
\\SYNACTIVE_CONSUMER_CHANGE\DLE\US\DC2\ESC\n\
\\ETBGET_TOPICS_OF_NAMESPACE\DLE \DC2$\n\
\ GET_TOPICS_OF_NAMESPACE_RESPONSE\DLE!\DC2\SO\n\
\\n\
\GET_SCHEMA\DLE\"\DC2\ETB\n\
\\DC3GET_SCHEMA_RESPONSE\DLE#\DC2\DC2\n\
\\SOAUTH_CHALLENGE\DLE$\DC2\DC1\n\
\\rAUTH_RESPONSE\DLE%\DC2\DLE\n\
\\fACK_RESPONSE\DLE&\DC2\CAN\n\
\\DC4GET_OR_CREATE_SCHEMA\DLE'\DC2!\n\
\\GSGET_OR_CREATE_SCHEMA_RESPONSE\DLE(\DC2\v\n\
\\aNEW_TXN\DLE2\DC2\DC4\n\
\\DLENEW_TXN_RESPONSE\DLE3\DC2\CAN\n\
\\DC4ADD_PARTITION_TO_TXN\DLE4\DC2!\n\
\\GSADD_PARTITION_TO_TXN_RESPONSE\DLE5\DC2\ESC\n\
\\ETBADD_SUBSCRIPTION_TO_TXN\DLE6\DC2$\n\
\ ADD_SUBSCRIPTION_TO_TXN_RESPONSE\DLE7\DC2\v\n\
\\aEND_TXN\DLE8\DC2\DC4\n\
\\DLEEND_TXN_RESPONSE\DLE9\DC2\CAN\n\
\\DC4END_TXN_ON_PARTITION\DLE:\DC2!\n\
\\GSEND_TXN_ON_PARTITION_RESPONSE\DLE;\DC2\ESC\n\
\\ETBEND_TXN_ON_SUBSCRIPTION\DLE<\DC2$\n\
\ END_TXN_ON_SUBSCRIPTION_RESPONSE\DLE=*D\n\
\\SICompressionType\DC2\b\n\
\\EOTNONE\DLE\NUL\DC2\a\n\
\\ETXLZ4\DLE\SOH\DC2\b\n\
\\EOTZLIB\DLE\STX\DC2\b\n\
\\EOTZSTD\DLE\ETX\DC2\n\
\\n\
\\ACKSNAPPY\DLE\EOT*\188\EOT\n\
\\vServerError\DC2\DLE\n\
\\fUnknownError\DLE\NUL\DC2\DC1\n\
\\rMetadataError\DLE\SOH\DC2\DC4\n\
\\DLEPersistenceError\DLE\STX\DC2\ETB\n\
\\DC3AuthenticationError\DLE\ETX\DC2\SYN\n\
\\DC2AuthorizationError\DLE\EOT\DC2\DLE\n\
\\fConsumerBusy\DLE\ENQ\DC2\DC3\n\
\\SIServiceNotReady\DLE\ACK\DC2%\n\
\!ProducerBlockedQuotaExceededError\DLE\a\DC2)\n\
\%ProducerBlockedQuotaExceededException\DLE\b\DC2\DC1\n\
\\rChecksumError\DLE\t\DC2\ESC\n\
\\ETBUnsupportedVersionError\DLE\n\
\\DC2\DC1\n\
\\rTopicNotFound\DLE\v\DC2\CAN\n\
\\DC4SubscriptionNotFound\DLE\f\DC2\DC4\n\
\\DLEConsumerNotFound\DLE\r\DC2\DC3\n\
\\SITooManyRequests\DLE\SO\DC2\CAN\n\
\\DC4TopicTerminatedError\DLE\SI\DC2\DLE\n\
\\fProducerBusy\DLE\DLE\DC2\DC4\n\
\\DLEInvalidTopicName\DLE\DC1\DC2\SYN\n\
\\DC2IncompatibleSchema\DLE\DC2\DC2\ETB\n\
\\DC3ConsumerAssignError\DLE\DC3\DC2\"\n\
\\RSTransactionCoordinatorNotFound\DLE\DC4\DC2\DC4\n\
\\DLEInvalidTxnStatus\DLE\NAK\DC2\DC3\n\
\\SINotAllowedError\DLE\SYN*K\n\
\\n\
\AuthMethod\DC2\DC2\n\
\\SOAuthMethodNone\DLE\NUL\DC2\DC3\n\
\\SIAuthMethodYcaV1\DLE\SOH\DC2\DC4\n\
\\DLEAuthMethodAthens\DLE\STX*\151\SOH\n\
\\SIProtocolVersion\DC2\ACK\n\
\\STXv0\DLE\NUL\DC2\ACK\n\
\\STXv1\DLE\SOH\DC2\ACK\n\
\\STXv2\DLE\STX\DC2\ACK\n\
\\STXv3\DLE\ETX\DC2\ACK\n\
\\STXv4\DLE\EOT\DC2\ACK\n\
\\STXv5\DLE\ENQ\DC2\ACK\n\
\\STXv6\DLE\ACK\DC2\ACK\n\
\\STXv7\DLE\a\DC2\ACK\n\
\\STXv8\DLE\b\DC2\ACK\n\
\\STXv9\DLE\t\DC2\a\n\
\\ETXv10\DLE\n\
\\DC2\a\n\
\\ETXv11\DLE\v\DC2\a\n\
\\ETXv12\DLE\f\DC2\a\n\
\\ETXv13\DLE\r\DC2\a\n\
\\ETXv14\DLE\SO\DC2\a\n\
\\ETXv15\DLE\SI*+\n\
\\rKeySharedMode\DC2\SO\n\
\\n\
\AUTO_SPLIT\DLE\NUL\DC2\n\
\\n\
\\ACKSTICKY\DLE\SOH*\"\n\
\\tTxnAction\DC2\n\
\\n\
\\ACKCOMMIT\DLE\NUL\DC2\t\n\
\\ENQABORT\DLE\SOHB&\n\
\\"org.apache.pulsar.common.api.protoH\ETXJ\237\219\STX\n\
\\a\DC2\ENQ\DC4\NUL\194\a\SOH\n\
\\253\ACK\n\
\\SOH\f\DC2\ETX\DC4\NUL\DC2\SUBm Source: https://raw.githubusercontent.com/apache/pulsar/master/pulsar-common/src/main/proto/PulsarApi.proto\n\
\2\131\ACK*\n\
\ Licensed to the Apache Software Foundation (ASF) under one\n\
\ or more contributor license agreements. See the NOTICE file\n\
\ distributed with this work for additional information\n\
\ regarding copyright ownership. The ASF licenses this file\n\
\ to you under the Apache License, Version 2.0 (the\n\
\ \"License\"); you may not use this file except in compliance\n\
\ with the License. You may obtain a copy of the License at\n\
\\n\
\ http://www.apache.org/licenses/LICENSE-2.0\n\
\\n\
\ Unless required by applicable law or agreed to in writing,\n\
\ software distributed under the License is distributed on an\n\
\ \"AS IS\" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY\n\
\ KIND, either express or implied. See the License for the\n\
\ specific language governing permissions and limitations\n\
\ under the License.\n\
\\n\
\\b\n\
\\SOH\STX\DC2\ETX\SYN\NUL\NAK\n\
\\b\n\
\\SOH\b\DC2\ETX\ETB\NUL;\n\
\\t\n\
\\STX\b\SOH\DC2\ETX\ETB\NUL;\n\
\\b\n\
\\SOH\b\DC2\ETX\CAN\NUL#\n\
\\t\n\
\\STX\b\t\DC2\ETX\CAN\NUL#\n\
\\n\
\\n\
\\STX\EOT\NUL\DC2\EOT\SUB\NUL3\SOH\n\
\\n\
\\n\
\\ETX\EOT\NUL\SOH\DC2\ETX\SUB\b\SO\n\
\\f\n\
\\EOT\EOT\NUL\EOT\NUL\DC2\EOT\ESC\EOT,\ENQ\n\
\\f\n\
\\ENQ\EOT\NUL\EOT\NUL\SOH\DC2\ETX\ESC\t\r\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\NUL\DC2\ETX\FS\b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\NUL\SOH\DC2\ETX\FS\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\NUL\STX\DC2\ETX\FS\SI\DLE\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\SOH\DC2\ETX\GS\b\DC3\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SOH\SOH\DC2\ETX\GS\b\SO\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SOH\STX\DC2\ETX\GS\DC1\DC2\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\STX\DC2\ETX\RS\b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\STX\SOH\DC2\ETX\RS\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\STX\STX\DC2\ETX\RS\SI\DLE\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\ETX\DC2\ETX\US\b\NAK\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ETX\SOH\DC2\ETX\US\b\DLE\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ETX\STX\DC2\ETX\US\DC3\DC4\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\EOT\DC2\ETX \b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\EOT\SOH\DC2\ETX \b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\EOT\STX\DC2\ETX \SI\DLE\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\ENQ\DC2\ETX!\b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ENQ\SOH\DC2\ETX!\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ENQ\STX\DC2\ETX!\SI\DLE\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\ACK\DC2\ETX\"\b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ACK\SOH\DC2\ETX\"\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\ACK\STX\DC2\ETX\"\SI\DLE\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\a\DC2\ETX#\b\DC2\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\a\SOH\DC2\ETX#\b\r\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\a\STX\DC2\ETX#\DLE\DC1\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\b\DC2\ETX$\b\DC2\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\b\SOH\DC2\ETX$\b\r\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\b\STX\DC2\ETX$\DLE\DC1\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\t\DC2\ETX%\b\DC2\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\t\SOH\DC2\ETX%\b\r\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\t\STX\DC2\ETX%\DLE\DC1\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\n\
\\DC2\ETX&\b\DC3\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\n\
\\SOH\DC2\ETX&\b\r\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\n\
\\STX\DC2\ETX&\DLE\DC2\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\v\DC2\ETX'\b\DC4\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\v\SOH\DC2\ETX'\b\SO\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\v\STX\DC2\ETX'\DC1\DC3\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\f\DC2\ETX(\b\DC2\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\f\SOH\DC2\ETX(\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\f\STX\DC2\ETX(\SI\DC1\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\r\DC2\ETX)\b\DC2\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\r\SOH\DC2\ETX)\b\f\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\r\STX\DC2\ETX)\SI\DC1\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\SO\DC2\ETX*\b\ETB\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SO\SOH\DC2\ETX*\b\DC1\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SO\STX\DC2\ETX*\DC4\SYN\n\
\\r\n\
\\ACK\EOT\NUL\EOT\NUL\STX\SI\DC2\ETX+\b\SYN\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SI\SOH\DC2\ETX+\b\DLE\n\
\\SO\n\
\\a\EOT\NUL\EOT\NUL\STX\SI\STX\DC2\ETX+\DC3\NAK\n\
\\v\n\
\\EOT\EOT\NUL\STX\NUL\DC2\ETX.\EOT\GS\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\EOT\DC2\ETX.\EOT\f\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\ENQ\DC2\ETX.\r\DC3\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\SOH\DC2\ETX.\DC4\CAN\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\ETX\DC2\ETX.\ESC\FS\n\
\\v\n\
\\EOT\EOT\NUL\STX\SOH\DC2\ETX/\EOT#\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\EOT\DC2\ETX/\EOT\f\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\ENQ\DC2\ETX/\r\DC2\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\SOH\DC2\ETX/\DC3\RS\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\ETX\DC2\ETX/!\"\n\
\\v\n\
\\EOT\EOT\NUL\STX\STX\DC2\ETX0\EOT\ESC\n\
\\f\n\
\\ENQ\EOT\NUL\STX\STX\EOT\DC2\ETX0\EOT\f\n\
\\f\n\
\\ENQ\EOT\NUL\STX\STX\ACK\DC2\ETX0\r\DC1\n\
\\f\n\
\\ENQ\EOT\NUL\STX\STX\SOH\DC2\ETX0\DC2\SYN\n\
\\f\n\
\\ENQ\EOT\NUL\STX\STX\ETX\DC2\ETX0\EM\SUB\n\
\\v\n\
\\EOT\EOT\NUL\STX\ETX\DC2\ETX1\EOT%\n\
\\f\n\
\\ENQ\EOT\NUL\STX\ETX\EOT\DC2\ETX1\EOT\f\n\
\\f\n\
\\ENQ\EOT\NUL\STX\ETX\ACK\DC2\ETX1\r\NAK\n\
\\f\n\
\\ENQ\EOT\NUL\STX\ETX\SOH\DC2\ETX1\SYN \n\
\\f\n\
\\ENQ\EOT\NUL\STX\ETX\ETX\DC2\ETX1#$\n\
\\n\
\\n\
\\STX\EOT\SOH\DC2\EOT5\NUL;\SOH\n\
\\n\
\\n\
\\ETX\EOT\SOH\SOH\DC2\ETX5\b\NAK\n\
\\v\n\
\\EOT\EOT\SOH\STX\NUL\DC2\ETX6\EOT!\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\EOT\DC2\ETX6\EOT\f\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\ENQ\DC2\ETX6\r\DC3\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\SOH\DC2\ETX6\DC4\FS\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\ETX\DC2\ETX6\US \n\
\\v\n\
\\EOT\EOT\SOH\STX\SOH\DC2\ETX7\EOT!\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\EOT\DC2\ETX7\EOT\f\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\ENQ\DC2\ETX7\r\DC3\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\SOH\DC2\ETX7\DC4\ESC\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\ETX\DC2\ETX7\US \n\
\\v\n\
\\EOT\EOT\SOH\STX\STX\DC2\ETX8\EOT0\n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\EOT\DC2\ETX8\EOT\f\n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\ENQ\DC2\ETX8\r\DC2\n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\SOH\DC2\ETX8\DC3\FS\n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\ETX\DC2\ETX8\US \n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\b\DC2\ETX8!/\n\
\\f\n\
\\ENQ\EOT\SOH\STX\STX\a\DC2\ETX8,.\n\
\\v\n\
\\EOT\EOT\SOH\STX\ETX\DC2\ETX9\EOT2\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\EOT\DC2\ETX9\EOT\f\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\ENQ\DC2\ETX9\r\DC2\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\SOH\DC2\ETX9\DC3\RS\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\ETX\DC2\ETX9!\"\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\b\DC2\ETX9#1\n\
\\f\n\
\\ENQ\EOT\SOH\STX\ETX\a\DC2\ETX9.0\n\
\\v\n\
\\EOT\EOT\SOH\STX\EOT\DC2\ETX:\EOT\US\n\
\\f\n\
\\ENQ\EOT\SOH\STX\EOT\EOT\DC2\ETX:\EOT\f\n\
\\f\n\
\\ENQ\EOT\SOH\STX\EOT\ENQ\DC2\ETX:\r\DC2\n\
\\f\n\
\\ENQ\EOT\SOH\STX\EOT\SOH\DC2\ETX:\DC3\SUB\n\
\\f\n\
\\ENQ\EOT\SOH\STX\EOT\ETX\DC2\ETX:\GS\RS\n\
\\n\
\\n\
\\STX\EOT\STX\DC2\EOT=\NUL@\SOH\n\
\\n\
\\n\
\\ETX\EOT\STX\SOH\DC2\ETX=\b\DLE\n\
\\v\n\
\\EOT\EOT\STX\STX\NUL\DC2\ETX>\EOT\FS\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\EOT\DC2\ETX>\EOT\f\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\ENQ\DC2\ETX>\r\DC3\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\SOH\DC2\ETX>\DC4\ETB\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\ETX\DC2\ETX>\SUB\ESC\n\
\\v\n\
\\EOT\EOT\STX\STX\SOH\DC2\ETX?\EOT\RS\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\EOT\DC2\ETX?\EOT\f\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\ENQ\DC2\ETX?\r\DC3\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\SOH\DC2\ETX?\DC4\EM\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\ETX\DC2\ETX?\FS\GS\n\
\\n\
\\n\
\\STX\EOT\ETX\DC2\EOTB\NULE\SOH\n\
\\n\
\\n\
\\ETX\EOT\ETX\SOH\DC2\ETXB\b\DC4\n\
\\v\n\
\\EOT\EOT\ETX\STX\NUL\DC2\ETXC\EOT\FS\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\EOT\DC2\ETXC\EOT\f\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\ENQ\DC2\ETXC\r\DC3\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\SOH\DC2\ETXC\DC4\ETB\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\ETX\DC2\ETXC\SUB\ESC\n\
\\v\n\
\\EOT\EOT\ETX\STX\SOH\DC2\ETXD\EOT\RS\n\
\\f\n\
\\ENQ\EOT\ETX\STX\SOH\EOT\DC2\ETXD\EOT\f\n\
\\f\n\
\\ENQ\EOT\ETX\STX\SOH\ENQ\DC2\ETXD\r\DC3\n\
\\f\n\
\\ENQ\EOT\ETX\STX\SOH\SOH\DC2\ETXD\DC4\EM\n\
\\f\n\
\\ENQ\EOT\ETX\STX\SOH\ETX\DC2\ETXD\FS\GS\n\
\\n\
\\n\
\\STX\EOT\EOT\DC2\EOTG\NULJ\SOH\n\
\\n\
\\n\
\\ETX\EOT\EOT\SOH\DC2\ETXG\b\DLE\n\
\\v\n\
\\EOT\EOT\EOT\STX\NUL\DC2\ETXH\EOT\GS\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\EOT\DC2\ETXH\EOT\f\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\ENQ\DC2\ETXH\r\DC2\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\SOH\DC2\ETXH\DC3\CAN\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\ETX\DC2\ETXH\ESC\FS\n\
\\v\n\
\\EOT\EOT\EOT\STX\SOH\DC2\ETXI\EOT\ESC\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\EOT\DC2\ETXI\EOT\f\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\ENQ\DC2\ETXI\r\DC2\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\SOH\DC2\ETXI\DC3\SYN\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\ETX\DC2\ETXI\EM\SUB\n\
\\n\
\\n\
\\STX\EOT\ENQ\DC2\EOTL\NULP\SOH\n\
\\n\
\\n\
\\ETX\EOT\ENQ\SOH\DC2\ETXL\b\SYN\n\
\\v\n\
\\EOT\EOT\ENQ\STX\NUL\DC2\ETXM\EOT\FS\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\EOT\DC2\ETXM\EOT\f\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\ENQ\DC2\ETXM\r\DC3\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\SOH\DC2\ETXM\DC4\ETB\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\ETX\DC2\ETXM\SUB\ESC\n\
\\v\n\
\\EOT\EOT\ENQ\STX\SOH\DC2\ETXN\EOT\GS\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\EOT\DC2\ETXN\EOT\f\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\ENQ\DC2\ETXN\r\DC2\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\SOH\DC2\ETXN\DC3\CAN\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\ETX\DC2\ETXN\ESC\FS\n\
\\v\n\
\\EOT\EOT\ENQ\STX\STX\DC2\ETXO\EOT#\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\STX\EOT\DC2\ETXO\EOT\f\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\STX\ACK\DC2\ETXO\r\NAK\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\STX\SOH\DC2\ETXO\SYN\RS\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\STX\ETX\DC2\ETXO!\"\n\
\\n\
\\n\
\\STX\ENQ\NUL\DC2\EOTR\NULX\SOH\n\
\\n\
\\n\
\\ETX\ENQ\NUL\SOH\DC2\ETXR\ENQ\DC4\n\
\\v\n\
\\EOT\ENQ\NUL\STX\NUL\DC2\ETXS\EOT\SI\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\NUL\SOH\DC2\ETXS\EOT\b\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\NUL\STX\DC2\ETXS\r\SO\n\
\\v\n\
\\EOT\ENQ\NUL\STX\SOH\DC2\ETXT\EOT\SI\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\SOH\SOH\DC2\ETXT\EOT\a\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\SOH\STX\DC2\ETXT\r\SO\n\
\\v\n\
\\EOT\ENQ\NUL\STX\STX\DC2\ETXU\EOT\SI\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\STX\SOH\DC2\ETXU\EOT\b\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\STX\STX\DC2\ETXU\r\SO\n\
\\v\n\
\\EOT\ENQ\NUL\STX\ETX\DC2\ETXV\EOT\SI\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\ETX\SOH\DC2\ETXV\EOT\b\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\ETX\STX\DC2\ETXV\r\SO\n\
\\v\n\
\\EOT\ENQ\NUL\STX\EOT\DC2\ETXW\EOT\DC1\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\EOT\SOH\DC2\ETXW\EOT\n\
\\n\
\\f\n\
\\ENQ\ENQ\NUL\STX\EOT\STX\DC2\ETXW\SI\DLE\n\
\\v\n\
\\STX\EOT\ACK\DC2\ENQZ\NUL\150\SOH\SOH\n\
\\n\
\\n\
\\ETX\EOT\ACK\SOH\DC2\ETXZ\b\ETB\n\
\\v\n\
\\EOT\EOT\ACK\STX\NUL\DC2\ETX[\EOT(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\EOT\DC2\ETX[\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\ENQ\DC2\ETX[\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\SOH\DC2\ETX[\DC4!\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\ETX\DC2\ETX[&'\n\
\\v\n\
\\EOT\EOT\ACK\STX\SOH\DC2\ETX\\\EOT(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\EOT\DC2\ETX\\\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\ENQ\DC2\ETX\\\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\SOH\DC2\ETX\\\DC4\US\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\ETX\DC2\ETX\\&'\n\
\\v\n\
\\EOT\EOT\ACK\STX\STX\DC2\ETX]\EOT(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\STX\EOT\DC2\ETX]\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\STX\ENQ\DC2\ETX]\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\STX\SOH\DC2\ETX]\DC4 \n\
\\f\n\
\\ENQ\EOT\ACK\STX\STX\ETX\DC2\ETX]&'\n\
\\v\n\
\\EOT\EOT\ACK\STX\ETX\DC2\ETX^\EOT(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ETX\EOT\DC2\ETX^\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ETX\ACK\DC2\ETX^\r\NAK\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ETX\SOH\DC2\ETX^\SYN \n\
\\f\n\
\\ENQ\EOT\ACK\STX\ETX\ETX\DC2\ETX^&'\n\
\T\n\
\\EOT\EOT\ACK\STX\EOT\DC2\ETXb\EOT(\SUBG Property set on replicated message,\n\
\ includes the source cluster name\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\EOT\EOT\DC2\ETXb\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\EOT\ENQ\DC2\ETXb\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\EOT\SOH\DC2\ETXb\DC4#\n\
\\f\n\
\\ENQ\EOT\ACK\STX\EOT\ETX\DC2\ETXb&'\n\
\1\n\
\\EOT\EOT\ACK\STX\ENQ\DC2\ETXd\EOT(\SUB$key to decide partition for the msg\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ENQ\EOT\DC2\ETXd\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ENQ\ENQ\DC2\ETXd\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ENQ\SOH\DC2\ETXd\DC4!\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ENQ\ETX\DC2\ETXd&'\n\
\/\n\
\\EOT\EOT\ACK\STX\ACK\DC2\ETXf\EOT(\SUB\" Override namespace's replication\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ACK\EOT\DC2\ETXf\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ACK\ENQ\DC2\ETXf\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\ACK\SOH\DC2\ETXf\DC4 \n\
\\f\n\
\\ENQ\EOT\ACK\STX\ACK\ETX\DC2\ETXf&'\n\
\\v\n\
\\EOT\EOT\ACK\STX\a\DC2\ETXg\EOT>\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\EOT\DC2\ETXg\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\ACK\DC2\ETXg\r\FS\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\SOH\DC2\ETXg\GS(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\ETX\DC2\ETXg+,\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\b\DC2\ETXg-=\n\
\\f\n\
\\ENQ\EOT\ACK\STX\a\a\DC2\ETXg8<\n\
\\v\n\
\\EOT\EOT\ACK\STX\b\DC2\ETXh\EOT8\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\EOT\DC2\ETXh\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\ENQ\DC2\ETXh\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\SOH\DC2\ETXh\DC4%\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\ETX\DC2\ETXh()\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\b\DC2\ETXh*7\n\
\\f\n\
\\ENQ\EOT\ACK\STX\b\a\DC2\ETXh56\n\
\\219\SOH\n\
\\EOT\EOT\ACK\STX\t\DC2\ETXm\EOT<\SUB\205\SOH Removed below checksum field from Metadata as\n\
\ it should be part of send-command which keeps checksum of header + payload\n\
\optional sfixed64 checksum = 10;\n\
\ differentiate single and batch message metadata\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\EOT\DC2\ETXm\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\ENQ\DC2\ETXm\r\DC2\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\SOH\DC2\ETXm\DC3(\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\ETX\DC2\ETXm+-\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\b\DC2\ETXm.;\n\
\\f\n\
\\ENQ\EOT\ACK\STX\t\a\DC2\ETXm9:\n\
\\177\SOH\n\
\\EOT\EOT\ACK\STX\n\
\\DC2\ETXq\EOT2\SUB\163\SOH the timestamp that this event occurs. it is typically set by applications.\n\
\ if this field is omitted, `publish_time` can be used for the purpose of `event_time`.\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\EOT\DC2\ETXq\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\ENQ\DC2\ETXq\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\SOH\DC2\ETXq\DC4\RS\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\ETX\DC2\ETXq!#\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\b\DC2\ETXq$1\n\
\\f\n\
\\ENQ\EOT\ACK\STX\n\
\\a\DC2\ETXq/0\n\
\[\n\
\\EOT\EOT\ACK\STX\v\DC2\ETXs\EOT1\SUBN Contains encryption key name, encrypted key and metadata to describe the key\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\v\EOT\DC2\ETXs\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\v\ACK\DC2\ETXs\r\ESC\n\
\\f\n\
\\ENQ\EOT\ACK\STX\v\SOH\DC2\ETXs\FS+\n\
\\f\n\
\\ENQ\EOT\ACK\STX\v\ETX\DC2\ETXs.0\n\
\1\n\
\\EOT\EOT\ACK\STX\f\DC2\ETXu\EOT)\SUB$ Algorithm used to encrypt data key\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\f\EOT\DC2\ETXu\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\f\ENQ\DC2\ETXu\r\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\f\SOH\DC2\ETXu\DC4#\n\
\\f\n\
\\ENQ\EOT\ACK\STX\f\ETX\DC2\ETXu&(\n\
\;\n\
\\EOT\EOT\ACK\STX\r\DC2\ETXw\EOT)\SUB. Additional parameters required by encryption\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\r\EOT\DC2\ETXw\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\r\ENQ\DC2\ETXw\r\DC2\n\
\\f\n\
\\ENQ\EOT\ACK\STX\r\SOH\DC2\ETXw\DC3#\n\
\\f\n\
\\ENQ\EOT\ACK\STX\r\ETX\DC2\ETXw&(\n\
\\v\n\
\\EOT\EOT\ACK\STX\SO\DC2\ETXx\EOT'\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SO\EOT\DC2\ETXx\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SO\ENQ\DC2\ETXx\r\DC2\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SO\SOH\DC2\ETXx\DC3!\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SO\ETX\DC2\ETXx$&\n\
\\v\n\
\\EOT\EOT\ACK\STX\SI\DC2\ETXz\EOTE\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\EOT\DC2\ETXz\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\ENQ\DC2\ETXz\r\DC1\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\SOH\DC2\ETXz\DC2+\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\ETX\DC2\ETXz.0\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\b\DC2\ETXz1D\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SI\a\DC2\ETXz=B\n\
\o\n\
\\EOT\EOT\ACK\STX\DLE\DC2\ETX|\EOT%\SUBb Specific a key to overwrite the message key which used for ordering dispatch in Key_Shared mode.\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DLE\EOT\DC2\ETX|\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DLE\ENQ\DC2\ETX|\r\DC2\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DLE\SOH\DC2\ETX|\DC3\US\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DLE\ETX\DC2\ETX|\"$\n\
\S\n\
\\EOT\EOT\ACK\STX\DC1\DC2\ETX\DEL\EOT(\SUBF Mark the message to be delivered at or after the specified timestamp\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DC1\EOT\DC2\ETX\DEL\EOT\f\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DC1\ENQ\DC2\ETX\DEL\r\DC2\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DC1\SOH\DC2\ETX\DEL\DC3\"\n\
\\f\n\
\\ENQ\EOT\ACK\STX\DC1\ETX\DC2\ETX\DEL%'\n\
\\190\SOH\n\
\\EOT\EOT\ACK\STX\DC2\DC2\EOT\132\SOH\EOT$\SUB\175\SOH Identify whether a message is a \"marker\" message used for\n\
\ internal metadata instead of application published data.\n\
\ Markers will generally not be propagated back to clients\n\
\\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC2\EOT\DC2\EOT\132\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC2\ENQ\DC2\EOT\132\SOH\r\DC2\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC2\SOH\DC2\EOT\132\SOH\DC3\RS\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC2\ETX\DC2\EOT\132\SOH!#\n\
\0\n\
\\EOT\EOT\ACK\STX\DC3\DC2\EOT\135\SOH\EOT*\SUB\" transaction related message info\n\
\\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC3\EOT\DC2\EOT\135\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC3\ENQ\DC2\EOT\135\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC3\SOH\DC2\EOT\135\SOH\DC4$\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC3\ETX\DC2\EOT\135\SOH')\n\
\\f\n\
\\EOT\EOT\ACK\STX\DC4\DC2\EOT\136\SOH\EOT)\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC4\EOT\DC2\EOT\136\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC4\ENQ\DC2\EOT\136\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC4\SOH\DC2\EOT\136\SOH\DC4#\n\
\\r\n\
\\ENQ\EOT\ACK\STX\DC4\ETX\DC2\EOT\136\SOH&(\n\
\[\n\
\\EOT\EOT\ACK\STX\NAK\DC2\EOT\139\SOH\EOT;\SUBM/ Add highest sequence id to support batch message with external sequence id\n\
\\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\EOT\DC2\EOT\139\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\ENQ\DC2\EOT\139\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\SOH\DC2\EOT\139\SOH\DC4'\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\ETX\DC2\EOT\139\SOH*,\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\b\DC2\EOT\139\SOH-:\n\
\\r\n\
\\ENQ\EOT\ACK\STX\NAK\a\DC2\EOT\139\SOH89\n\
\<\n\
\\EOT\EOT\ACK\STX\SYN\DC2\EOT\142\SOH\EOT6\SUB. Indicate if the message payload value is set\n\
\\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\EOT\DC2\EOT\142\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\ENQ\DC2\EOT\142\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\SOH\DC2\EOT\142\SOH\DC2\FS\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\ETX\DC2\EOT\142\SOH\US!\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\b\DC2\EOT\142\SOH\"5\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SYN\a\DC2\EOT\142\SOH.3\n\
\\f\n\
\\EOT\EOT\ACK\STX\ETB\DC2\EOT\143\SOH\EOT\RS\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ETB\EOT\DC2\EOT\143\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ETB\ENQ\DC2\EOT\143\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ETB\SOH\DC2\EOT\143\SOH\DC4\CAN\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ETB\ETX\DC2\EOT\143\SOH\ESC\GS\n\
\\f\n\
\\EOT\EOT\ACK\STX\CAN\DC2\EOT\144\SOH\b0\n\
\\r\n\
\\ENQ\EOT\ACK\STX\CAN\EOT\DC2\EOT\144\SOH\b\DLE\n\
\\r\n\
\\ENQ\EOT\ACK\STX\CAN\ENQ\DC2\EOT\144\SOH\DC1\SYN\n\
\\r\n\
\\ENQ\EOT\ACK\STX\CAN\SOH\DC2\EOT\144\SOH\ETB*\n\
\\r\n\
\\ENQ\EOT\ACK\STX\CAN\ETX\DC2\EOT\144\SOH-/\n\
\\f\n\
\\EOT\EOT\ACK\STX\EM\DC2\EOT\145\SOH\b1\n\
\\r\n\
\\ENQ\EOT\ACK\STX\EM\EOT\DC2\EOT\145\SOH\b\DLE\n\
\\r\n\
\\ENQ\EOT\ACK\STX\EM\ENQ\DC2\EOT\145\SOH\DC1\SYN\n\
\\r\n\
\\ENQ\EOT\ACK\STX\EM\SOH\DC2\EOT\145\SOH\ETB+\n\
\\r\n\
\\ENQ\EOT\ACK\STX\EM\ETX\DC2\EOT\145\SOH.0\n\
\\f\n\
\\EOT\EOT\ACK\STX\SUB\DC2\EOT\146\SOH\b%\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SUB\EOT\DC2\EOT\146\SOH\b\DLE\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SUB\ENQ\DC2\EOT\146\SOH\DC1\SYN\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SUB\SOH\DC2\EOT\146\SOH\ETB\US\n\
\\r\n\
\\ENQ\EOT\ACK\STX\SUB\ETX\DC2\EOT\146\SOH\"$\n\
\<\n\
\\EOT\EOT\ACK\STX\ESC\DC2\EOT\149\SOH\EOT<\SUB. Indicate if the message partition key is set\n\
\\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\EOT\DC2\EOT\149\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\ENQ\DC2\EOT\149\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\SOH\DC2\EOT\149\SOH\DC2$\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\ETX\DC2\EOT\149\SOH')\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\b\DC2\EOT\149\SOH*;\n\
\\r\n\
\\ENQ\EOT\ACK\STX\ESC\a\DC2\EOT\149\SOH5:\n\
\\f\n\
\\STX\EOT\a\DC2\ACK\152\SOH\NUL\170\SOH\SOH\n\
\\v\n\
\\ETX\EOT\a\SOH\DC2\EOT\152\SOH\b\GS\n\
\\f\n\
\\EOT\EOT\a\STX\NUL\DC2\EOT\153\SOH\EOT(\n\
\\r\n\
\\ENQ\EOT\a\STX\NUL\EOT\DC2\EOT\153\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\NUL\ACK\DC2\EOT\153\SOH\r\NAK\n\
\\r\n\
\\ENQ\EOT\a\STX\NUL\SOH\DC2\EOT\153\SOH\SYN \n\
\\r\n\
\\ENQ\EOT\a\STX\NUL\ETX\DC2\EOT\153\SOH&'\n\
\\f\n\
\\EOT\EOT\a\STX\SOH\DC2\EOT\154\SOH\EOT(\n\
\\r\n\
\\ENQ\EOT\a\STX\SOH\EOT\DC2\EOT\154\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\SOH\ENQ\DC2\EOT\154\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\a\STX\SOH\SOH\DC2\EOT\154\SOH\DC4!\n\
\\r\n\
\\ENQ\EOT\a\STX\SOH\ETX\DC2\EOT\154\SOH&'\n\
\\f\n\
\\EOT\EOT\a\STX\STX\DC2\EOT\155\SOH\EOT'\n\
\\r\n\
\\ENQ\EOT\a\STX\STX\EOT\DC2\EOT\155\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\STX\ENQ\DC2\EOT\155\SOH\r\DC2\n\
\\r\n\
\\ENQ\EOT\a\STX\STX\SOH\DC2\EOT\155\SOH\DC3\US\n\
\\r\n\
\\ENQ\EOT\a\STX\STX\ETX\DC2\EOT\155\SOH%&\n\
\\f\n\
\\EOT\EOT\a\STX\ETX\DC2\EOT\156\SOH\EOT:\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\EOT\DC2\EOT\156\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\ENQ\DC2\EOT\156\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\SOH\DC2\EOT\156\SOH\DC2\US\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\ETX\DC2\EOT\156\SOH&'\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\b\DC2\EOT\156\SOH(9\n\
\\r\n\
\\ENQ\EOT\a\STX\ETX\a\DC2\EOT\156\SOH38\n\
\\178\SOH\n\
\\EOT\EOT\a\STX\EOT\DC2\EOT\160\SOH\EOT1\SUB\163\SOH the timestamp that this event occurs. it is typically set by applications.\n\
\ if this field is omitted, `publish_time` can be used for the purpose of `event_time`.\n\
\\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\EOT\DC2\EOT\160\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\ENQ\DC2\EOT\160\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\SOH\DC2\EOT\160\SOH\DC4\RS\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\ETX\DC2\EOT\160\SOH!\"\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\b\DC2\EOT\160\SOH#0\n\
\\r\n\
\\ENQ\EOT\a\STX\EOT\a\DC2\EOT\160\SOH./\n\
\\f\n\
\\EOT\EOT\a\STX\ENQ\DC2\EOT\161\SOH\EOTD\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\EOT\DC2\EOT\161\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\ENQ\DC2\EOT\161\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\SOH\DC2\EOT\161\SOH\DC2+\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\ETX\DC2\EOT\161\SOH./\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\b\DC2\EOT\161\SOH0C\n\
\\r\n\
\\ENQ\EOT\a\STX\ENQ\a\DC2\EOT\161\SOH<A\n\
\p\n\
\\EOT\EOT\a\STX\ACK\DC2\EOT\163\SOH\EOT$\SUBb Specific a key to overwrite the message key which used for ordering dispatch in Key_Shared mode.\n\
\\n\
\\r\n\
\\ENQ\EOT\a\STX\ACK\EOT\DC2\EOT\163\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\ACK\ENQ\DC2\EOT\163\SOH\r\DC2\n\
\\r\n\
\\ENQ\EOT\a\STX\ACK\SOH\DC2\EOT\163\SOH\DC3\US\n\
\\r\n\
\\ENQ\EOT\a\STX\ACK\ETX\DC2\EOT\163\SOH\"#\n\
\O\n\
\\EOT\EOT\a\STX\a\DC2\EOT\165\SOH\EOT$\SUBA Allows consumer retrieve the sequence id that the producer set.\n\
\\n\
\\r\n\
\\ENQ\EOT\a\STX\a\EOT\DC2\EOT\165\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\a\ENQ\DC2\EOT\165\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\a\STX\a\SOH\DC2\EOT\165\SOH\DC4\US\n\
\\r\n\
\\ENQ\EOT\a\STX\a\ETX\DC2\EOT\165\SOH\"#\n\
\<\n\
\\EOT\EOT\a\STX\b\DC2\EOT\167\SOH\EOT5\SUB. Indicate if the message payload value is set\n\
\\n\
\\r\n\
\\ENQ\EOT\a\STX\b\EOT\DC2\EOT\167\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\b\ENQ\DC2\EOT\167\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\a\STX\b\SOH\DC2\EOT\167\SOH\DC2\FS\n\
\\r\n\
\\ENQ\EOT\a\STX\b\ETX\DC2\EOT\167\SOH\US \n\
\\r\n\
\\ENQ\EOT\a\STX\b\b\DC2\EOT\167\SOH!4\n\
\\r\n\
\\ENQ\EOT\a\STX\b\a\DC2\EOT\167\SOH-2\n\
\<\n\
\\EOT\EOT\a\STX\t\DC2\EOT\169\SOH\EOT=\SUB. Indicate if the message partition key is set\n\
\\n\
\\r\n\
\\ENQ\EOT\a\STX\t\EOT\DC2\EOT\169\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\a\STX\t\ENQ\DC2\EOT\169\SOH\r\DC1\n\
\\r\n\
\\ENQ\EOT\a\STX\t\SOH\DC2\EOT\169\SOH\DC2$\n\
\\r\n\
\\ENQ\EOT\a\STX\t\ETX\DC2\EOT\169\SOH')\n\
\\r\n\
\\ENQ\EOT\a\STX\t\b\DC2\EOT\169\SOH*<\n\
\\r\n\
\\ENQ\EOT\a\STX\t\a\DC2\EOT\169\SOH6;\n\
\\f\n\
\\STX\ENQ\SOH\DC2\ACK\172\SOH\NUL\201\SOH\SOH\n\
\\v\n\
\\ETX\ENQ\SOH\SOH\DC2\EOT\172\SOH\ENQ\DLE\n\
\\f\n\
\\EOT\ENQ\SOH\STX\NUL\DC2\EOT\173\SOH\EOT\FS\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\NUL\SOH\DC2\EOT\173\SOH\EOT\DLE\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\NUL\STX\DC2\EOT\173\SOH\SUB\ESC\n\
\&\n\
\\EOT\ENQ\SOH\STX\SOH\DC2\EOT\174\SOH\EOT\FS\"\CAN Error with ZK/metadata\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SOH\SOH\DC2\EOT\174\SOH\EOT\DC1\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SOH\STX\DC2\EOT\174\SOH\SUB\ESC\n\
\-\n\
\\EOT\ENQ\SOH\STX\STX\DC2\EOT\175\SOH\EOT\FS\"\US Error writing reading from BK\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\STX\SOH\DC2\EOT\175\SOH\EOT\DC4\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\STX\STX\DC2\EOT\175\SOH\SUB\ESC\n\
\(\n\
\\EOT\ENQ\SOH\STX\ETX\DC2\EOT\176\SOH\EOT\FS\"\SUB Non valid authentication\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ETX\SOH\DC2\EOT\176\SOH\EOT\ETB\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ETX\STX\DC2\EOT\176\SOH\SUB\ESC\n\
\.\n\
\\EOT\ENQ\SOH\STX\EOT\DC2\EOT\177\SOH\EOT\FS\" Not authorized to use resource\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\EOT\SOH\DC2\EOT\177\SOH\EOT\SYN\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\EOT\STX\DC2\EOT\177\SOH\SUB\ESC\n\
\7\n\
\\EOT\ENQ\SOH\STX\ENQ\DC2\EOT\179\SOH\EOT\FS\") Unable to subscribe/unsubscribe because\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ENQ\SOH\DC2\EOT\179\SOH\EOT\DLE\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ENQ\STX\DC2\EOT\179\SOH\SUB\ESC\n\
\s\n\
\\EOT\ENQ\SOH\STX\ACK\DC2\EOT\181\SOH\EOT\FS\SUB\US other consumers are connected\n\
\\"D Any error that requires client retry operation with a fresh lookup\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ACK\SOH\DC2\EOT\181\SOH\EOT\DC3\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\ACK\STX\DC2\EOT\181\SOH\SUB\ESC\n\
\H\n\
\\EOT\ENQ\SOH\STX\a\DC2\EOT\182\SOH\EOT*\": Unable to create producer because backlog quota exceeded\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\a\SOH\DC2\EOT\182\SOH\EOT%\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\a\STX\DC2\EOT\182\SOH()\n\
\H\n\
\\EOT\ENQ\SOH\STX\b\DC2\EOT\183\SOH\EOT.\": Exception while creating producer because quota exceeded\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\b\SOH\DC2\EOT\183\SOH\EOT)\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\b\STX\DC2\EOT\183\SOH,-\n\
\6\n\
\\EOT\ENQ\SOH\STX\t\DC2\EOT\184\SOH\EOT\SYN\"( Error while verifying message checksum\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\t\SOH\DC2\EOT\184\SOH\EOT\DC1\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\t\STX\DC2\EOT\184\SOH\DC4\NAK\n\
\U\n\
\\EOT\ENQ\SOH\STX\n\
\\DC2\EOT\185\SOH\EOT!\"G Error when an older client/version doesn't support a required feature\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\n\
\\SOH\DC2\EOT\185\SOH\EOT\ESC\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\n\
\\STX\DC2\EOT\185\SOH\RS \n\
\\US\n\
\\EOT\ENQ\SOH\STX\v\DC2\EOT\186\SOH\EOT\ETB\"\DC1 Topic not found\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\v\SOH\DC2\EOT\186\SOH\EOT\DC1\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\v\STX\DC2\EOT\186\SOH\DC4\SYN\n\
\&\n\
\\EOT\ENQ\SOH\STX\f\DC2\EOT\187\SOH\EOT\RS\"\CAN Subscription not found\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\f\SOH\DC2\EOT\187\SOH\EOT\CAN\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\f\STX\DC2\EOT\187\SOH\ESC\GS\n\
\\"\n\
\\EOT\ENQ\SOH\STX\r\DC2\EOT\188\SOH\EOT\SUB\"\DC4 Consumer not found\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\r\SOH\DC2\EOT\188\SOH\EOT\DC4\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\r\STX\DC2\EOT\188\SOH\ETB\EM\n\
\:\n\
\\EOT\ENQ\SOH\STX\SO\DC2\EOT\189\SOH\EOT\EM\", Error with too many simultaneously request\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SO\SOH\DC2\EOT\189\SOH\EOT\DC3\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SO\STX\DC2\EOT\189\SOH\SYN\CAN\n\
\-\n\
\\EOT\ENQ\SOH\STX\SI\DC2\EOT\190\SOH\EOT\RS\"\US The topic has been terminated\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SI\SOH\DC2\EOT\190\SOH\EOT\CAN\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SI\STX\DC2\EOT\190\SOH\ESC\GS\n\
\<\n\
\\EOT\ENQ\SOH\STX\DLE\DC2\EOT\192\SOH\EOT\RS\". Producer with same name is already connected\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DLE\SOH\DC2\EOT\192\SOH\EOT\DLE\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DLE\STX\DC2\EOT\192\SOH\ESC\GS\n\
\+\n\
\\EOT\ENQ\SOH\STX\DC1\DC2\EOT\193\SOH\EOT\SUB\"\GS The topic name is not valid\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC1\SOH\DC2\EOT\193\SOH\EOT\DC4\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC1\STX\DC2\EOT\193\SOH\ETB\EM\n\
\C\n\
\\EOT\ENQ\SOH\STX\DC2\DC2\EOT\195\SOH\EOT\FS\"5 Specified schema was incompatible with topic schema\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC2\SOH\DC2\EOT\195\SOH\EOT\SYN\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC2\STX\DC2\EOT\195\SOH\EM\ESC\n\
\0\n\
\\EOT\ENQ\SOH\STX\DC3\DC2\EOT\196\SOH\EOT\GS\"\" Dispatcher assign consumer error\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC3\SOH\DC2\EOT\196\SOH\EOT\ETB\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC3\STX\DC2\EOT\196\SOH\SUB\FS\n\
\7\n\
\\EOT\ENQ\SOH\STX\DC4\DC2\EOT\198\SOH\EOT(\") Transaction coordinator not found error\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC4\SOH\DC2\EOT\198\SOH\EOT\"\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\DC4\STX\DC2\EOT\198\SOH%'\n\
\(\n\
\\EOT\ENQ\SOH\STX\NAK\DC2\EOT\199\SOH\EOT\SUB\"\SUB Invalid txn status error\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\NAK\SOH\DC2\EOT\199\SOH\EOT\DC4\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\NAK\STX\DC2\EOT\199\SOH\ETB\EM\n\
\!\n\
\\EOT\ENQ\SOH\STX\SYN\DC2\EOT\200\SOH\EOT\EM\"\DC3 Not allowed error\n\
\\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SYN\SOH\DC2\EOT\200\SOH\EOT\DC3\n\
\\r\n\
\\ENQ\ENQ\SOH\STX\SYN\STX\DC2\EOT\200\SOH\SYN\CAN\n\
\\f\n\
\\STX\ENQ\STX\DC2\ACK\203\SOH\NUL\207\SOH\SOH\n\
\\v\n\
\\ETX\ENQ\STX\SOH\DC2\EOT\203\SOH\ENQ\SI\n\
\\f\n\
\\EOT\ENQ\STX\STX\NUL\DC2\EOT\204\SOH\EOT\EM\n\
\\r\n\
\\ENQ\ENQ\STX\STX\NUL\SOH\DC2\EOT\204\SOH\EOT\DC2\n\
\\r\n\
\\ENQ\ENQ\STX\STX\NUL\STX\DC2\EOT\204\SOH\ETB\CAN\n\
\\f\n\
\\EOT\ENQ\STX\STX\SOH\DC2\EOT\205\SOH\EOT\EM\n\
\\r\n\
\\ENQ\ENQ\STX\STX\SOH\SOH\DC2\EOT\205\SOH\EOT\DC3\n\
\\r\n\
\\ENQ\ENQ\STX\STX\SOH\STX\DC2\EOT\205\SOH\ETB\CAN\n\
\\f\n\
\\EOT\ENQ\STX\STX\STX\DC2\EOT\206\SOH\EOT\EM\n\
\\r\n\
\\ENQ\ENQ\STX\STX\STX\SOH\DC2\EOT\206\SOH\EOT\DC4\n\
\\r\n\
\\ENQ\ENQ\STX\STX\STX\STX\DC2\EOT\206\SOH\ETB\CAN\n\
\i\n\
\\STX\ENQ\ETX\DC2\ACK\211\SOH\NUL\231\SOH\SOH\SUB[ Each protocol version identify new features that are\n\
\ incrementally added to the protocol\n\
\\n\
\\v\n\
\\ETX\ENQ\ETX\SOH\DC2\EOT\211\SOH\ENQ\DC4\n\
\\"\n\
\\EOT\ENQ\ETX\STX\NUL\DC2\EOT\212\SOH\EOT\v\"\DC4 Initial versioning\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\NUL\SOH\DC2\EOT\212\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\NUL\STX\DC2\EOT\212\SOH\t\n\
\\n\
\,\n\
\\EOT\ENQ\ETX\STX\SOH\DC2\EOT\213\SOH\EOT\v\"\RS Added application keep-alive\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SOH\SOH\DC2\EOT\213\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SOH\STX\DC2\EOT\213\SOH\t\n\
\\n\
\=\n\
\\EOT\ENQ\ETX\STX\STX\DC2\EOT\214\SOH\EOT\v\"/ Added RedeliverUnacknowledgedMessages Command\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\STX\SOH\DC2\EOT\214\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\STX\STX\DC2\EOT\214\SOH\t\n\
\\n\
\3\n\
\\EOT\ENQ\ETX\STX\ETX\DC2\EOT\215\SOH\EOT\v\"% Added compression with LZ4 and ZLib\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ETX\SOH\DC2\EOT\215\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ETX\STX\DC2\EOT\215\SOH\t\n\
\\n\
\+\n\
\\EOT\ENQ\ETX\STX\EOT\DC2\EOT\216\SOH\EOT\v\"\GS Added batch message support\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\EOT\SOH\DC2\EOT\216\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\EOT\STX\DC2\EOT\216\SOH\t\n\
\\n\
\>\n\
\\EOT\ENQ\ETX\STX\ENQ\DC2\EOT\217\SOH\EOT\v\"0 Added disconnect client w/o closing connection\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ENQ\SOH\DC2\EOT\217\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ENQ\STX\DC2\EOT\217\SOH\t\n\
\\n\
\A\n\
\\EOT\ENQ\ETX\STX\ACK\DC2\EOT\218\SOH\EOT\v\"3 Added checksum computation for metadata + payload\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ACK\SOH\DC2\EOT\218\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\ACK\STX\DC2\EOT\218\SOH\t\n\
\\n\
\8\n\
\\EOT\ENQ\ETX\STX\a\DC2\EOT\219\SOH\EOT\v\"* Added CommandLookupTopic - Binary Lookup\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\a\SOH\DC2\EOT\219\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\a\STX\DC2\EOT\219\SOH\t\n\
\\n\
\V\n\
\\EOT\ENQ\ETX\STX\b\DC2\EOT\220\SOH\EOT\v\"H Added CommandConsumerStats - Client fetches broker side consumer stats\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\b\SOH\DC2\EOT\220\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\b\STX\DC2\EOT\220\SOH\t\n\
\\n\
\/\n\
\\EOT\ENQ\ETX\STX\t\DC2\EOT\221\SOH\EOT\v\"! Added end of topic notification\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\t\SOH\DC2\EOT\221\SOH\EOT\ACK\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\t\STX\DC2\EOT\221\SOH\t\n\
\\n\
\%\n\
\\EOT\ENQ\ETX\STX\n\
\\DC2\EOT\222\SOH\EOT\r\"\ETB Added proxy to broker\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\n\
\\SOH\DC2\EOT\222\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\n\
\\STX\DC2\EOT\222\SOH\n\
\\f\n\
\_\n\
\\EOT\ENQ\ETX\STX\v\DC2\EOT\223\SOH\EOT\r\"Q C++ consumers before this version are not correctly handling the checksum field\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\v\SOH\DC2\EOT\223\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\v\STX\DC2\EOT\223\SOH\n\
\\f\n\
\<\n\
\\EOT\ENQ\ETX\STX\f\DC2\EOT\224\SOH\EOT\r\". Added get topic's last messageId from broker\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\f\SOH\DC2\EOT\224\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\f\STX\DC2\EOT\224\SOH\n\
\\f\n\
\\139\SOH\n\
\\EOT\ENQ\ETX\STX\r\DC2\EOT\227\SOH\EOT\r\SUBF Added CommandActiveConsumerChange\n\
\ Added CommandGetTopicsOfNamespace\n\
\\"5 Schema-registry : added avro schema format for json\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\r\SOH\DC2\EOT\227\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\r\STX\DC2\EOT\227\SOH\n\
\\f\n\
\P\n\
\\EOT\ENQ\ETX\STX\SO\DC2\EOT\228\SOH\EOT\r\"B Add CommandAuthChallenge and CommandAuthResponse for mutual auth\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SO\SOH\DC2\EOT\228\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SO\STX\DC2\EOT\228\SOH\n\
\\f\n\
\r\n\
\\EOT\ENQ\ETX\STX\SI\DC2\EOT\230\SOH\EOT\r\SUB\US Added Key_Shared subscription\n\
\\"C Add CommandGetOrCreateSchema and CommandGetOrCreateSchemaResponse\n\
\\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SI\SOH\DC2\EOT\230\SOH\EOT\a\n\
\\r\n\
\\ENQ\ENQ\ETX\STX\SI\STX\DC2\EOT\230\SOH\n\
\\f\n\
\\f\n\
\\STX\EOT\b\DC2\ACK\233\SOH\NUL\129\STX\SOH\n\
\\v\n\
\\ETX\EOT\b\SOH\DC2\EOT\233\SOH\b\SYN\n\
\\f\n\
\\EOT\EOT\b\STX\NUL\DC2\EOT\234\SOH\EOT'\n\
\\r\n\
\\ENQ\EOT\b\STX\NUL\EOT\DC2\EOT\234\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\NUL\ENQ\DC2\EOT\234\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\NUL\SOH\DC2\EOT\234\SOH\DC4\"\n\
\\r\n\
\\ENQ\EOT\b\STX\NUL\ETX\DC2\EOT\234\SOH%&\n\
\;\n\
\\EOT\EOT\b\STX\SOH\DC2\EOT\235\SOH\EOT(\"- Deprecated. Use \"auth_method_name\" instead.\n\
\\n\
\\r\n\
\\ENQ\EOT\b\STX\SOH\EOT\DC2\EOT\235\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\SOH\ACK\DC2\EOT\235\SOH\r\ETB\n\
\\r\n\
\\ENQ\EOT\b\STX\SOH\SOH\DC2\EOT\235\SOH\CAN#\n\
\\r\n\
\\ENQ\EOT\b\STX\SOH\ETX\DC2\EOT\235\SOH&'\n\
\\f\n\
\\EOT\EOT\b\STX\STX\DC2\EOT\236\SOH\EOT)\n\
\\r\n\
\\ENQ\EOT\b\STX\STX\EOT\DC2\EOT\236\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\STX\ENQ\DC2\EOT\236\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\STX\SOH\DC2\EOT\236\SOH\DC4$\n\
\\r\n\
\\ENQ\EOT\b\STX\STX\ETX\DC2\EOT\236\SOH'(\n\
\\f\n\
\\EOT\EOT\b\STX\ETX\DC2\EOT\237\SOH\EOT!\n\
\\r\n\
\\ENQ\EOT\b\STX\ETX\EOT\DC2\EOT\237\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\ETX\ENQ\DC2\EOT\237\SOH\r\DC2\n\
\\r\n\
\\ENQ\EOT\b\STX\ETX\SOH\DC2\EOT\237\SOH\DC3\FS\n\
\\r\n\
\\ENQ\EOT\b\STX\ETX\ETX\DC2\EOT\237\SOH\US \n\
\\f\n\
\\EOT\EOT\b\STX\EOT\DC2\EOT\238\SOH\EOT6\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\EOT\DC2\EOT\238\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\ENQ\DC2\EOT\238\SOH\r\DC2\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\SOH\DC2\EOT\238\SOH\DC3#\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\ETX\DC2\EOT\238\SOH&'\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\b\DC2\EOT\238\SOH(5\n\
\\r\n\
\\ENQ\EOT\b\STX\EOT\a\DC2\EOT\238\SOH34\n\
\j\n\
\\EOT\EOT\b\STX\ENQ\DC2\EOT\242\SOH\EOT,\SUB\\ Client can ask to be proxyied to a specific broker\n\
\ This is only honored by a Pulsar proxy\n\
\\n\
\\r\n\
\\ENQ\EOT\b\STX\ENQ\EOT\DC2\EOT\242\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\ENQ\ENQ\DC2\EOT\242\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\ENQ\SOH\DC2\EOT\242\SOH\DC4'\n\
\\r\n\
\\ENQ\EOT\b\STX\ENQ\ETX\DC2\EOT\242\SOH*+\n\
\\144\SOH\n\
\\EOT\EOT\b\STX\ACK\DC2\EOT\247\SOH\EOT+\SUB\129\SOH Original principal that was verified by\n\
\ a Pulsar proxy. In this case the auth info above\n\
\ will be the auth of the proxy itself\n\
\\n\
\\r\n\
\\ENQ\EOT\b\STX\ACK\EOT\DC2\EOT\247\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\ACK\ENQ\DC2\EOT\247\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\ACK\SOH\DC2\EOT\247\SOH\DC4&\n\
\\r\n\
\\ENQ\EOT\b\STX\ACK\ETX\DC2\EOT\247\SOH)*\n\
\\153\SOH\n\
\\EOT\EOT\b\STX\a\DC2\EOT\252\SOH\EOT+\SUB\138\SOH Original auth role and auth Method that was passed\n\
\ to the proxy. In this case the auth info above\n\
\ will be the auth of the proxy itself\n\
\\n\
\\r\n\
\\ENQ\EOT\b\STX\a\EOT\DC2\EOT\252\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\a\ENQ\DC2\EOT\252\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\a\SOH\DC2\EOT\252\SOH\DC4&\n\
\\r\n\
\\ENQ\EOT\b\STX\a\ETX\DC2\EOT\252\SOH)*\n\
\\f\n\
\\EOT\EOT\b\STX\b\DC2\EOT\253\SOH\EOT-\n\
\\r\n\
\\ENQ\EOT\b\STX\b\EOT\DC2\EOT\253\SOH\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\b\ENQ\DC2\EOT\253\SOH\r\DC3\n\
\\r\n\
\\ENQ\EOT\b\STX\b\SOH\DC2\EOT\253\SOH\DC4(\n\
\\r\n\
\\ENQ\EOT\b\STX\b\ETX\DC2\EOT\253\SOH+,\n\
\\GS\n\
\\EOT\EOT\b\STX\t\DC2\EOT\128\STX\EOT-\SUB\SI Feature flags\n\
\\n\
\\r\n\
\\ENQ\EOT\b\STX\t\EOT\DC2\EOT\128\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\b\STX\t\ACK\DC2\EOT\128\STX\r\EM\n\
\\r\n\
\\ENQ\EOT\b\STX\t\SOH\DC2\EOT\128\STX\SUB'\n\
\\r\n\
\\ENQ\EOT\b\STX\t\ETX\DC2\EOT\128\STX*,\n\
\\f\n\
\\STX\EOT\t\DC2\ACK\131\STX\NUL\133\STX\SOH\n\
\\v\n\
\\ETX\EOT\t\SOH\DC2\EOT\131\STX\b\DC4\n\
\\f\n\
\\EOT\EOT\t\STX\NUL\DC2\EOT\132\STX\STX<\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\EOT\DC2\EOT\132\STX\STX\n\
\\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\ENQ\DC2\EOT\132\STX\v\SI\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\SOH\DC2\EOT\132\STX\DLE%\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\ETX\DC2\EOT\132\STX()\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\b\DC2\EOT\132\STX*;\n\
\\r\n\
\\ENQ\EOT\t\STX\NUL\a\DC2\EOT\132\STX5:\n\
\\f\n\
\\STX\EOT\n\
\\DC2\ACK\135\STX\NUL\139\STX\SOH\n\
\\v\n\
\\ETX\EOT\n\
\\SOH\DC2\EOT\135\STX\b\CAN\n\
\\f\n\
\\EOT\EOT\n\
\\STX\NUL\DC2\EOT\136\STX\EOT'\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\NUL\EOT\DC2\EOT\136\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\NUL\ENQ\DC2\EOT\136\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\NUL\SOH\DC2\EOT\136\STX\DC4\"\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\NUL\ETX\DC2\EOT\136\STX%&\n\
\\f\n\
\\EOT\EOT\n\
\\STX\SOH\DC2\EOT\137\STX\EOT6\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\EOT\DC2\EOT\137\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\ENQ\DC2\EOT\137\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\SOH\DC2\EOT\137\STX\DC3#\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\ETX\DC2\EOT\137\STX&'\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\b\DC2\EOT\137\STX(5\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\SOH\a\DC2\EOT\137\STX34\n\
\\f\n\
\\EOT\EOT\n\
\\STX\STX\DC2\EOT\138\STX\EOT(\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\STX\EOT\DC2\EOT\138\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\STX\ENQ\DC2\EOT\138\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\STX\SOH\DC2\EOT\138\STX\DC3#\n\
\\r\n\
\\ENQ\EOT\n\
\\STX\STX\ETX\DC2\EOT\138\STX&'\n\
\\f\n\
\\STX\EOT\v\DC2\ACK\141\STX\NUL\145\STX\SOH\n\
\\v\n\
\\ETX\EOT\v\SOH\DC2\EOT\141\STX\b\ESC\n\
\\f\n\
\\EOT\EOT\v\STX\NUL\DC2\EOT\142\STX\EOT'\n\
\\r\n\
\\ENQ\EOT\v\STX\NUL\EOT\DC2\EOT\142\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\v\STX\NUL\ENQ\DC2\EOT\142\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\v\STX\NUL\SOH\DC2\EOT\142\STX\DC4\"\n\
\\r\n\
\\ENQ\EOT\v\STX\NUL\ETX\DC2\EOT\142\STX%&\n\
\\f\n\
\\EOT\EOT\v\STX\SOH\DC2\EOT\143\STX\EOT#\n\
\\r\n\
\\ENQ\EOT\v\STX\SOH\EOT\DC2\EOT\143\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\v\STX\SOH\ACK\DC2\EOT\143\STX\r\NAK\n\
\\r\n\
\\ENQ\EOT\v\STX\SOH\SOH\DC2\EOT\143\STX\SYN\RS\n\
\\r\n\
\\ENQ\EOT\v\STX\SOH\ETX\DC2\EOT\143\STX!\"\n\
\\f\n\
\\EOT\EOT\v\STX\STX\DC2\EOT\144\STX\EOT6\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\EOT\DC2\EOT\144\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\ENQ\DC2\EOT\144\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\SOH\DC2\EOT\144\STX\DC3#\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\ETX\DC2\EOT\144\STX&'\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\b\DC2\EOT\144\STX(5\n\
\\r\n\
\\ENQ\EOT\v\STX\STX\a\DC2\EOT\144\STX34\n\
\\f\n\
\\STX\EOT\f\DC2\ACK\147\STX\NUL\151\STX\SOH\n\
\\v\n\
\\ETX\EOT\f\SOH\DC2\EOT\147\STX\b\FS\n\
\\f\n\
\\EOT\EOT\f\STX\NUL\DC2\EOT\148\STX\EOT'\n\
\\r\n\
\\ENQ\EOT\f\STX\NUL\EOT\DC2\EOT\148\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\f\STX\NUL\ENQ\DC2\EOT\148\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\f\STX\NUL\SOH\DC2\EOT\148\STX\DC4\"\n\
\\r\n\
\\ENQ\EOT\f\STX\NUL\ETX\DC2\EOT\148\STX%&\n\
\\f\n\
\\EOT\EOT\f\STX\SOH\DC2\EOT\149\STX\EOT$\n\
\\r\n\
\\ENQ\EOT\f\STX\SOH\EOT\DC2\EOT\149\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\f\STX\SOH\ACK\DC2\EOT\149\STX\r\NAK\n\
\\r\n\
\\ENQ\EOT\f\STX\SOH\SOH\DC2\EOT\149\STX\SYN\US\n\
\\r\n\
\\ENQ\EOT\f\STX\SOH\ETX\DC2\EOT\149\STX\"#\n\
\\f\n\
\\EOT\EOT\f\STX\STX\DC2\EOT\150\STX\EOT6\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\EOT\DC2\EOT\150\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\ENQ\DC2\EOT\150\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\SOH\DC2\EOT\150\STX\DC3#\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\ETX\DC2\EOT\150\STX&'\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\b\DC2\EOT\150\STX(5\n\
\\r\n\
\\ENQ\EOT\f\STX\STX\a\DC2\EOT\150\STX34\n\
\g\n\
\\STX\EOT\r\DC2\ACK\154\STX\NUL\157\STX\SOH\SUBY To support mutual authentication type, such as Sasl, reuse this command to mutual auth.\n\
\\n\
\\v\n\
\\ETX\EOT\r\SOH\DC2\EOT\154\STX\b\DLE\n\
\\f\n\
\\EOT\EOT\r\STX\NUL\DC2\EOT\155\STX\EOT)\n\
\\r\n\
\\ENQ\EOT\r\STX\NUL\EOT\DC2\EOT\155\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\r\STX\NUL\ENQ\DC2\EOT\155\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\r\STX\NUL\SOH\DC2\EOT\155\STX\DC4$\n\
\\r\n\
\\ENQ\EOT\r\STX\NUL\ETX\DC2\EOT\155\STX'(\n\
\\f\n\
\\EOT\EOT\r\STX\SOH\DC2\EOT\156\STX\EOT!\n\
\\r\n\
\\ENQ\EOT\r\STX\SOH\EOT\DC2\EOT\156\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\r\STX\SOH\ENQ\DC2\EOT\156\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\r\STX\SOH\SOH\DC2\EOT\156\STX\DC3\FS\n\
\\r\n\
\\ENQ\EOT\r\STX\SOH\ETX\DC2\EOT\156\STX\US \n\
\\f\n\
\\STX\ENQ\EOT\DC2\ACK\159\STX\NUL\162\STX\SOH\n\
\\v\n\
\\ETX\ENQ\EOT\SOH\DC2\EOT\159\STX\ENQ\DC2\n\
\\f\n\
\\EOT\ENQ\EOT\STX\NUL\DC2\EOT\160\STX\EOT\DC3\n\
\\r\n\
\\ENQ\ENQ\EOT\STX\NUL\SOH\DC2\EOT\160\STX\EOT\SO\n\
\\r\n\
\\ENQ\ENQ\EOT\STX\NUL\STX\DC2\EOT\160\STX\DC1\DC2\n\
\\f\n\
\\EOT\ENQ\EOT\STX\SOH\DC2\EOT\161\STX\EOT\SI\n\
\\r\n\
\\ENQ\ENQ\EOT\STX\SOH\SOH\DC2\EOT\161\STX\EOT\n\
\\n\
\\r\n\
\\ENQ\ENQ\EOT\STX\SOH\STX\DC2\EOT\161\STX\r\SO\n\
\\f\n\
\\STX\EOT\SO\DC2\ACK\164\STX\NUL\168\STX\SOH\n\
\\v\n\
\\ETX\EOT\SO\SOH\DC2\EOT\164\STX\b\NAK\n\
\\f\n\
\\EOT\EOT\SO\STX\NUL\DC2\EOT\165\STX\EOT-\n\
\\r\n\
\\ENQ\EOT\SO\STX\NUL\EOT\DC2\EOT\165\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SO\STX\NUL\ACK\DC2\EOT\165\STX\r\SUB\n\
\\r\n\
\\ENQ\EOT\SO\STX\NUL\SOH\DC2\EOT\165\STX\ESC(\n\
\\r\n\
\\ENQ\EOT\SO\STX\NUL\ETX\DC2\EOT\165\STX+,\n\
\\f\n\
\\EOT\EOT\SO\STX\SOH\DC2\EOT\166\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SO\STX\SOH\EOT\DC2\EOT\166\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SO\STX\SOH\ACK\DC2\EOT\166\STX\r\NAK\n\
\\r\n\
\\ENQ\EOT\SO\STX\SOH\SOH\DC2\EOT\166\STX\SYN \n\
\\r\n\
\\ENQ\EOT\SO\STX\SOH\ETX\DC2\EOT\166\STX#$\n\
\\f\n\
\\EOT\EOT\SO\STX\STX\DC2\EOT\167\STX\EOT@\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\EOT\DC2\EOT\167\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\ENQ\DC2\EOT\167\STX\r\DC1\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\SOH\DC2\EOT\167\STX\DC2)\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\ETX\DC2\EOT\167\STX,-\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\b\DC2\EOT\167\STX.?\n\
\\r\n\
\\ENQ\EOT\SO\STX\STX\a\DC2\EOT\167\STX9>\n\
\\f\n\
\\STX\EOT\SI\DC2\ACK\170\STX\NUL\226\STX\SOH\n\
\\v\n\
\\ETX\EOT\SI\SOH\DC2\EOT\170\STX\b\CAN\n\
\\SO\n\
\\EOT\EOT\SI\EOT\NUL\DC2\ACK\171\STX\EOT\176\STX\ENQ\n\
\\r\n\
\\ENQ\EOT\SI\EOT\NUL\SOH\DC2\EOT\171\STX\t\DLE\n\
\\SO\n\
\\ACK\EOT\SI\EOT\NUL\STX\NUL\DC2\EOT\172\STX\b\SYN\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\NUL\SOH\DC2\EOT\172\STX\b\DC1\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\NUL\STX\DC2\EOT\172\STX\DC4\NAK\n\
\\SO\n\
\\ACK\EOT\SI\EOT\NUL\STX\SOH\DC2\EOT\173\STX\b\SYN\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\SOH\SOH\DC2\EOT\173\STX\b\SO\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\SOH\STX\DC2\EOT\173\STX\DC4\NAK\n\
\\SO\n\
\\ACK\EOT\SI\EOT\NUL\STX\STX\DC2\EOT\174\STX\b\SYN\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\STX\SOH\DC2\EOT\174\STX\b\DLE\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\STX\STX\DC2\EOT\174\STX\DC4\NAK\n\
\\SO\n\
\\ACK\EOT\SI\EOT\NUL\STX\ETX\DC2\EOT\175\STX\b\ETB\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\ETX\SOH\DC2\EOT\175\STX\b\DC2\n\
\\SI\n\
\\a\EOT\SI\EOT\NUL\STX\ETX\STX\DC2\EOT\175\STX\NAK\SYN\n\
\\f\n\
\\EOT\EOT\SI\STX\NUL\DC2\EOT\177\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SI\STX\NUL\EOT\DC2\EOT\177\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\NUL\ENQ\DC2\EOT\177\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\NUL\SOH\DC2\EOT\177\STX\DC4\EM\n\
\\r\n\
\\ENQ\EOT\SI\STX\NUL\ETX\DC2\EOT\177\STX#$\n\
\\f\n\
\\EOT\EOT\SI\STX\SOH\DC2\EOT\178\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SI\STX\SOH\EOT\DC2\EOT\178\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\SOH\ENQ\DC2\EOT\178\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\SOH\SOH\DC2\EOT\178\STX\DC4 \n\
\\r\n\
\\ENQ\EOT\SI\STX\SOH\ETX\DC2\EOT\178\STX#$\n\
\\f\n\
\\EOT\EOT\SI\STX\STX\DC2\EOT\179\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SI\STX\STX\EOT\DC2\EOT\179\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\STX\ACK\DC2\EOT\179\STX\r\DC4\n\
\\r\n\
\\ENQ\EOT\SI\STX\STX\SOH\DC2\EOT\179\STX\NAK\FS\n\
\\r\n\
\\ENQ\EOT\SI\STX\STX\ETX\DC2\EOT\179\STX#$\n\
\\f\n\
\\EOT\EOT\SI\STX\ETX\DC2\EOT\181\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SI\STX\ETX\EOT\DC2\EOT\181\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\ETX\ENQ\DC2\EOT\181\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\ETX\SOH\DC2\EOT\181\STX\DC4\US\n\
\\r\n\
\\ENQ\EOT\SI\STX\ETX\ETX\DC2\EOT\181\STX#$\n\
\\f\n\
\\EOT\EOT\SI\STX\EOT\DC2\EOT\182\STX\EOT%\n\
\\r\n\
\\ENQ\EOT\SI\STX\EOT\EOT\DC2\EOT\182\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\EOT\ENQ\DC2\EOT\182\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\EOT\SOH\DC2\EOT\182\STX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\SI\STX\EOT\ETX\DC2\EOT\182\STX#$\n\
\\f\n\
\\EOT\EOT\SI\STX\ENQ\DC2\EOT\183\STX\EOT&\n\
\\r\n\
\\ENQ\EOT\SI\STX\ENQ\EOT\DC2\EOT\183\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\ENQ\ENQ\DC2\EOT\183\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\ENQ\SOH\DC2\EOT\183\STX\DC4!\n\
\\r\n\
\\ENQ\EOT\SI\STX\ENQ\ETX\DC2\EOT\183\STX$%\n\
\\f\n\
\\EOT\EOT\SI\STX\ACK\DC2\EOT\184\STX\EOT&\n\
\\r\n\
\\ENQ\EOT\SI\STX\ACK\EOT\DC2\EOT\184\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\ACK\ENQ\DC2\EOT\184\STX\r\DC2\n\
\\r\n\
\\ENQ\EOT\SI\STX\ACK\SOH\DC2\EOT\184\STX\DC3!\n\
\\r\n\
\\ENQ\EOT\SI\STX\ACK\ETX\DC2\EOT\184\STX$%\n\
\[\n\
\\EOT\EOT\SI\STX\a\DC2\EOT\188\STX\EOT/\SUBM Signal wether the subscription should be backed by a\n\
\ durable cursor or not\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\EOT\DC2\EOT\188\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\ENQ\DC2\EOT\188\STX\r\DC1\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\SOH\DC2\EOT\188\STX\DC2\EM\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\ETX\DC2\EOT\188\STX\FS\GS\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\b\DC2\EOT\188\STX\RS.\n\
\\r\n\
\\ENQ\EOT\SI\STX\a\a\DC2\EOT\188\STX)-\n\
\\165\SOH\n\
\\EOT\EOT\SI\STX\b\DC2\EOT\193\STX\EOT0\SUB\150\SOH If specified, the subscription will position the cursor\n\
\ markd-delete position on the particular message id and\n\
\ will send messages from that point\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\b\EOT\DC2\EOT\193\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\b\ACK\DC2\EOT\193\STX\r\SUB\n\
\\r\n\
\\ENQ\EOT\SI\STX\b\SOH\DC2\EOT\193\STX\ESC+\n\
\\r\n\
\\ENQ\EOT\SI\STX\b\ETX\DC2\EOT\193\STX./\n\
\A\n\
\\EOT\EOT\SI\STX\t\DC2\EOT\196\STX\EOT$\SUB3/ Add optional metadata key=value to this consumer\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\t\EOT\DC2\EOT\196\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\t\ACK\DC2\EOT\196\STX\r\NAK\n\
\\r\n\
\\ENQ\EOT\SI\STX\t\SOH\DC2\EOT\196\STX\SYN\RS\n\
\\r\n\
\\ENQ\EOT\SI\STX\t\ETX\DC2\EOT\196\STX!#\n\
\\f\n\
\\EOT\EOT\SI\STX\n\
\\DC2\EOT\198\STX\EOT&\n\
\\r\n\
\\ENQ\EOT\SI\STX\n\
\\EOT\DC2\EOT\198\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\n\
\\ENQ\DC2\EOT\198\STX\r\DC1\n\
\\r\n\
\\ENQ\EOT\SI\STX\n\
\\SOH\DC2\EOT\198\STX\DC2 \n\
\\r\n\
\\ENQ\EOT\SI\STX\n\
\\ETX\DC2\EOT\198\STX#%\n\
\\f\n\
\\EOT\EOT\SI\STX\v\DC2\EOT\200\STX\EOT \n\
\\r\n\
\\ENQ\EOT\SI\STX\v\EOT\DC2\EOT\200\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\v\ACK\DC2\EOT\200\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\v\SOH\DC2\EOT\200\STX\DC4\SUB\n\
\\r\n\
\\ENQ\EOT\SI\STX\v\ETX\DC2\EOT\200\STX\GS\US\n\
\\SO\n\
\\EOT\EOT\SI\EOT\SOH\DC2\ACK\201\STX\EOT\204\STX\ENQ\n\
\\r\n\
\\ENQ\EOT\SI\EOT\SOH\SOH\DC2\EOT\201\STX\t\CAN\n\
\\SO\n\
\\ACK\EOT\SI\EOT\SOH\STX\NUL\DC2\EOT\202\STX\b\NAK\n\
\\SI\n\
\\a\EOT\SI\EOT\SOH\STX\NUL\SOH\DC2\EOT\202\STX\b\SO\n\
\\SI\n\
\\a\EOT\SI\EOT\SOH\STX\NUL\STX\DC2\EOT\202\STX\DC3\DC4\n\
\\SO\n\
\\ACK\EOT\SI\EOT\SOH\STX\SOH\DC2\EOT\203\STX\b\NAK\n\
\\SI\n\
\\a\EOT\SI\EOT\SOH\STX\SOH\SOH\DC2\EOT\203\STX\b\DLE\n\
\\SI\n\
\\a\EOT\SI\EOT\SOH\STX\SOH\STX\DC2\EOT\203\STX\DC3\DC4\n\
\]\n\
\\EOT\EOT\SI\STX\f\DC2\EOT\207\STX\EOTE\SUBO Signal whether the subscription will initialize on latest\n\
\ or not -- earliest\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\EOT\DC2\EOT\207\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\ACK\DC2\EOT\207\STX\r\FS\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\SOH\DC2\EOT\207\STX\GS,\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\ETX\DC2\EOT\207\STX/1\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\b\DC2\EOT\207\STX2D\n\
\\r\n\
\\ENQ\EOT\SI\STX\f\a\DC2\EOT\207\STX=C\n\
\\194\SOH\n\
\\EOT\EOT\SI\STX\r\DC2\EOT\212\STX\EOT4\SUB\179\SOH Mark the subscription as \"replicated\". Pulsar will make sure\n\
\ to periodically sync the state of replicated subscriptions\n\
\ across different clusters (when using geo-replication).\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\r\EOT\DC2\EOT\212\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\r\ENQ\DC2\EOT\212\STX\r\DC1\n\
\\r\n\
\\ENQ\EOT\SI\STX\r\SOH\DC2\EOT\212\STX\DC2.\n\
\\r\n\
\\ENQ\EOT\SI\STX\r\ETX\DC2\EOT\212\STX13\n\
\\238\SOH\n\
\\EOT\EOT\SI\STX\SO\DC2\EOT\219\STX\EOT=\SUB\223\SOH If true, the subscribe operation will cause a topic to be\n\
\ created if it does not exist already (and if topic auto-creation\n\
\ is allowed by broker.\n\
\ If false, the subscribe operation will fail if the topic\n\
\ does not exist.\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\EOT\DC2\EOT\219\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\ENQ\DC2\EOT\219\STX\r\DC1\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\SOH\DC2\EOT\219\STX\DC2&\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\ETX\DC2\EOT\219\STX)+\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\b\DC2\EOT\219\STX,<\n\
\\r\n\
\\ENQ\EOT\SI\STX\SO\a\DC2\EOT\219\STX7;\n\
\\143\SOH\n\
\\EOT\EOT\SI\STX\SI\DC2\EOT\223\STX\EOTK\SUB\128\SOH If specified, the subscription will reset cursor's position back\n\
\ to specified seconds and will send messages from that point\n\
\\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\EOT\DC2\EOT\223\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\ENQ\DC2\EOT\223\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\SOH\DC2\EOT\223\STX\DC47\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\ETX\DC2\EOT\223\STX:<\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\b\DC2\EOT\223\STX=J\n\
\\r\n\
\\ENQ\EOT\SI\STX\SI\a\DC2\EOT\223\STXHI\n\
\\f\n\
\\EOT\EOT\SI\STX\DLE\DC2\EOT\225\STX\EOT.\n\
\\r\n\
\\ENQ\EOT\SI\STX\DLE\EOT\DC2\EOT\225\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SI\STX\DLE\ACK\DC2\EOT\225\STX\r\SUB\n\
\\r\n\
\\ENQ\EOT\SI\STX\DLE\SOH\DC2\EOT\225\STX\ESC(\n\
\\r\n\
\\ENQ\EOT\SI\STX\DLE\ETX\DC2\EOT\225\STX+-\n\
\\f\n\
\\STX\EOT\DLE\DC2\ACK\228\STX\NUL\240\STX\SOH\n\
\\v\n\
\\ETX\EOT\DLE\SOH\DC2\EOT\228\STX\b'\n\
\\f\n\
\\EOT\EOT\DLE\STX\NUL\DC2\EOT\229\STX\EOT)\n\
\\r\n\
\\ENQ\EOT\DLE\STX\NUL\EOT\DC2\EOT\229\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DLE\STX\NUL\ENQ\DC2\EOT\229\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DLE\STX\NUL\SOH\DC2\EOT\229\STX\DC4\EM\n\
\\r\n\
\\ENQ\EOT\DLE\STX\NUL\ETX\DC2\EOT\229\STX'(\n\
\\f\n\
\\EOT\EOT\DLE\STX\SOH\DC2\EOT\230\STX\EOT)\n\
\\r\n\
\\ENQ\EOT\DLE\STX\SOH\EOT\DC2\EOT\230\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DLE\STX\SOH\ENQ\DC2\EOT\230\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DLE\STX\SOH\SOH\DC2\EOT\230\STX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DLE\STX\SOH\ETX\DC2\EOT\230\STX'(\n\
\\149\SOH\n\
\\EOT\EOT\DLE\STX\STX\DC2\EOT\234\STX\EOT+\SUB\134\SOH TODO - Remove original_principal, original_auth_data, original_auth_method\n\
\ Original principal that was verified by\n\
\ a Pulsar proxy.\n\
\\n\
\\r\n\
\\ENQ\EOT\DLE\STX\STX\EOT\DC2\EOT\234\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DLE\STX\STX\ENQ\DC2\EOT\234\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DLE\STX\STX\SOH\DC2\EOT\234\STX\DC4&\n\
\\r\n\
\\ENQ\EOT\DLE\STX\STX\ETX\DC2\EOT\234\STX)*\n\
\Q\n\
\\EOT\EOT\DLE\STX\ETX\DC2\EOT\238\STX\EOT+\SUBC Original auth role and auth Method that was passed\n\
\ to the proxy.\n\
\\n\
\\r\n\
\\ENQ\EOT\DLE\STX\ETX\EOT\DC2\EOT\238\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DLE\STX\ETX\ENQ\DC2\EOT\238\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DLE\STX\ETX\SOH\DC2\EOT\238\STX\DC4&\n\
\\r\n\
\\ENQ\EOT\DLE\STX\ETX\ETX\DC2\EOT\238\STX)*\n\
\\f\n\
\\EOT\EOT\DLE\STX\EOT\DC2\EOT\239\STX\EOT-\n\
\\r\n\
\\ENQ\EOT\DLE\STX\EOT\EOT\DC2\EOT\239\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DLE\STX\EOT\ENQ\DC2\EOT\239\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DLE\STX\EOT\SOH\DC2\EOT\239\STX\DC4(\n\
\\r\n\
\\ENQ\EOT\DLE\STX\EOT\ETX\DC2\EOT\239\STX+,\n\
\\f\n\
\\STX\EOT\DC1\DC2\ACK\242\STX\NUL\252\STX\SOH\n\
\\v\n\
\\ETX\EOT\DC1\SOH\DC2\EOT\242\STX\b/\n\
\\SO\n\
\\EOT\EOT\DC1\EOT\NUL\DC2\ACK\243\STX\EOT\246\STX\ENQ\n\
\\r\n\
\\ENQ\EOT\DC1\EOT\NUL\SOH\DC2\EOT\243\STX\t\DC3\n\
\\SO\n\
\\ACK\EOT\DC1\EOT\NUL\STX\NUL\DC2\EOT\244\STX\b\NAK\n\
\\SI\n\
\\a\EOT\DC1\EOT\NUL\STX\NUL\SOH\DC2\EOT\244\STX\b\SI\n\
\\SI\n\
\\a\EOT\DC1\EOT\NUL\STX\NUL\STX\DC2\EOT\244\STX\DC3\DC4\n\
\\SO\n\
\\ACK\EOT\DC1\EOT\NUL\STX\SOH\DC2\EOT\245\STX\b\NAK\n\
\\SI\n\
\\a\EOT\DC1\EOT\NUL\STX\SOH\SOH\DC2\EOT\245\STX\b\SO\n\
\\SI\n\
\\a\EOT\DC1\EOT\NUL\STX\SOH\STX\DC2\EOT\245\STX\DC3\DC4\n\
\)\n\
\\EOT\EOT\DC1\STX\NUL\DC2\EOT\247\STX\EOT.\"\ESC Optional in case of error\n\
\\n\
\\r\n\
\\ENQ\EOT\DC1\STX\NUL\EOT\DC2\EOT\247\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC1\STX\NUL\ENQ\DC2\EOT\247\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC1\STX\NUL\SOH\DC2\EOT\247\STX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DC1\STX\NUL\ETX\DC2\EOT\247\STX,-\n\
\\f\n\
\\EOT\EOT\DC1\STX\SOH\DC2\EOT\248\STX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC1\STX\SOH\EOT\DC2\EOT\248\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC1\STX\SOH\ENQ\DC2\EOT\248\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC1\STX\SOH\SOH\DC2\EOT\248\STX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DC1\STX\SOH\ETX\DC2\EOT\248\STX,-\n\
\\f\n\
\\EOT\EOT\DC1\STX\STX\DC2\EOT\249\STX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC1\STX\STX\EOT\DC2\EOT\249\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC1\STX\STX\ACK\DC2\EOT\249\STX\r\ETB\n\
\\r\n\
\\ENQ\EOT\DC1\STX\STX\SOH\DC2\EOT\249\STX\CAN \n\
\\r\n\
\\ENQ\EOT\DC1\STX\STX\ETX\DC2\EOT\249\STX,-\n\
\\f\n\
\\EOT\EOT\DC1\STX\ETX\DC2\EOT\250\STX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC1\STX\ETX\EOT\DC2\EOT\250\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC1\STX\ETX\ACK\DC2\EOT\250\STX\r\CAN\n\
\\r\n\
\\ENQ\EOT\DC1\STX\ETX\SOH\DC2\EOT\250\STX\EM\RS\n\
\\r\n\
\\ENQ\EOT\DC1\STX\ETX\ETX\DC2\EOT\250\STX,-\n\
\\f\n\
\\EOT\EOT\DC1\STX\EOT\DC2\EOT\251\STX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC1\STX\EOT\EOT\DC2\EOT\251\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC1\STX\EOT\ENQ\DC2\EOT\251\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC1\STX\EOT\SOH\DC2\EOT\251\STX\DC4\ESC\n\
\\r\n\
\\ENQ\EOT\DC1\STX\EOT\ETX\DC2\EOT\251\STX,-\n\
\\f\n\
\\STX\EOT\DC2\DC2\ACK\254\STX\NUL\142\ETX\SOH\n\
\\v\n\
\\ETX\EOT\DC2\SOH\DC2\EOT\254\STX\b\SUB\n\
\\f\n\
\\EOT\EOT\DC2\STX\NUL\DC2\EOT\255\STX\EOT)\n\
\\r\n\
\\ENQ\EOT\DC2\STX\NUL\EOT\DC2\EOT\255\STX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\NUL\ENQ\DC2\EOT\255\STX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\NUL\SOH\DC2\EOT\255\STX\DC4\EM\n\
\\r\n\
\\ENQ\EOT\DC2\STX\NUL\ETX\DC2\EOT\255\STX'(\n\
\\f\n\
\\EOT\EOT\DC2\STX\SOH\DC2\EOT\128\ETX\EOT)\n\
\\r\n\
\\ENQ\EOT\DC2\STX\SOH\EOT\DC2\EOT\128\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\SOH\ENQ\DC2\EOT\128\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\SOH\SOH\DC2\EOT\128\ETX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DC2\STX\SOH\ETX\DC2\EOT\128\ETX'(\n\
\\f\n\
\\EOT\EOT\DC2\STX\STX\DC2\EOT\129\ETX\EOT;\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\EOT\DC2\EOT\129\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\ENQ\DC2\EOT\129\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\SOH\DC2\EOT\129\ETX\DC2\US\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\ETX\DC2\EOT\129\ETX'(\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\b\DC2\EOT\129\ETX):\n\
\\r\n\
\\ENQ\EOT\DC2\STX\STX\a\DC2\EOT\129\ETX49\n\
\\149\SOH\n\
\\EOT\EOT\DC2\STX\ETX\DC2\EOT\134\ETX\EOT+\SUB\134\SOH TODO - Remove original_principal, original_auth_data, original_auth_method\n\
\ Original principal that was verified by\n\
\ a Pulsar proxy.\n\
\\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ETX\EOT\DC2\EOT\134\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ETX\ENQ\DC2\EOT\134\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ETX\SOH\DC2\EOT\134\ETX\DC4&\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ETX\ETX\DC2\EOT\134\ETX)*\n\
\Q\n\
\\EOT\EOT\DC2\STX\EOT\DC2\EOT\138\ETX\EOT+\SUBC Original auth role and auth Method that was passed\n\
\ to the proxy.\n\
\\n\
\\r\n\
\\ENQ\EOT\DC2\STX\EOT\EOT\DC2\EOT\138\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\EOT\ENQ\DC2\EOT\138\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\EOT\SOH\DC2\EOT\138\ETX\DC4&\n\
\\r\n\
\\ENQ\EOT\DC2\STX\EOT\ETX\DC2\EOT\138\ETX)*\n\
\\f\n\
\\EOT\EOT\DC2\STX\ENQ\DC2\EOT\139\ETX\EOT-\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ENQ\EOT\DC2\EOT\139\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ENQ\ENQ\DC2\EOT\139\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ENQ\SOH\DC2\EOT\139\ETX\DC4(\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ENQ\ETX\DC2\EOT\139\ETX+,\n\
\\SI\n\
\\EOT\EOT\DC2\STX\ACK\DC2\EOT\141\ETX\EOT1\SUB\SOH\n\
\\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ACK\EOT\DC2\EOT\141\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ACK\ENQ\DC2\EOT\141\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ACK\SOH\DC2\EOT\141\ETX\DC4,\n\
\\r\n\
\\ENQ\EOT\DC2\STX\ACK\ETX\DC2\EOT\141\ETX/0\n\
\\f\n\
\\STX\EOT\DC3\DC2\ACK\144\ETX\NUL\163\ETX\SOH\n\
\\v\n\
\\ETX\EOT\DC3\SOH\DC2\EOT\144\ETX\b\"\n\
\\SO\n\
\\EOT\EOT\DC3\EOT\NUL\DC2\ACK\145\ETX\EOT\149\ETX\ENQ\n\
\\r\n\
\\ENQ\EOT\DC3\EOT\NUL\SOH\DC2\EOT\145\ETX\t\DC3\n\
\\SO\n\
\\ACK\EOT\DC3\EOT\NUL\STX\NUL\DC2\EOT\146\ETX\b\NAK\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\NUL\SOH\DC2\EOT\146\ETX\b\DLE\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\NUL\STX\DC2\EOT\146\ETX\DC3\DC4\n\
\\SO\n\
\\ACK\EOT\DC3\EOT\NUL\STX\SOH\DC2\EOT\147\ETX\b\NAK\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\SOH\SOH\DC2\EOT\147\ETX\b\SI\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\SOH\STX\DC2\EOT\147\ETX\DC3\DC4\n\
\\SO\n\
\\ACK\EOT\DC3\EOT\NUL\STX\STX\DC2\EOT\148\ETX\b\NAK\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\STX\SOH\DC2\EOT\148\ETX\b\SO\n\
\\SI\n\
\\a\EOT\DC3\EOT\NUL\STX\STX\STX\DC2\EOT\148\ETX\DC3\DC4\n\
\)\n\
\\EOT\EOT\DC3\STX\NUL\DC2\EOT\151\ETX\EOT.\"\ESC Optional in case of error\n\
\\n\
\\r\n\
\\ENQ\EOT\DC3\STX\NUL\EOT\DC2\EOT\151\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\NUL\ENQ\DC2\EOT\151\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC3\STX\NUL\SOH\DC2\EOT\151\ETX\DC4$\n\
\\r\n\
\\ENQ\EOT\DC3\STX\NUL\ETX\DC2\EOT\151\ETX,-\n\
\\f\n\
\\EOT\EOT\DC3\STX\SOH\DC2\EOT\152\ETX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC3\STX\SOH\EOT\DC2\EOT\152\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\SOH\ENQ\DC2\EOT\152\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC3\STX\SOH\SOH\DC2\EOT\152\ETX\DC4'\n\
\\r\n\
\\ENQ\EOT\DC3\STX\SOH\ETX\DC2\EOT\152\ETX,-\n\
\\f\n\
\\EOT\EOT\DC3\STX\STX\DC2\EOT\153\ETX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC3\STX\STX\EOT\DC2\EOT\153\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\STX\ACK\DC2\EOT\153\ETX\r\ETB\n\
\\r\n\
\\ENQ\EOT\DC3\STX\STX\SOH\DC2\EOT\153\ETX\CAN \n\
\\r\n\
\\ENQ\EOT\DC3\STX\STX\ETX\DC2\EOT\153\ETX,-\n\
\\f\n\
\\EOT\EOT\DC3\STX\ETX\DC2\EOT\154\ETX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ETX\EOT\DC2\EOT\154\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ETX\ENQ\DC2\EOT\154\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ETX\SOH\DC2\EOT\154\ETX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ETX\ETX\DC2\EOT\154\ETX,-\n\
\\f\n\
\\EOT\EOT\DC3\STX\EOT\DC2\EOT\155\ETX\EOT@\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\EOT\DC2\EOT\155\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\ENQ\DC2\EOT\155\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\SOH\DC2\EOT\155\ETX\DC2\US\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\ETX\DC2\EOT\155\ETX,-\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\b\DC2\EOT\155\ETX.?\n\
\\r\n\
\\ENQ\EOT\DC3\STX\EOT\a\DC2\EOT\155\ETX9>\n\
\\f\n\
\\EOT\EOT\DC3\STX\ENQ\DC2\EOT\156\ETX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ENQ\EOT\DC2\EOT\156\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ENQ\ACK\DC2\EOT\156\ETX\r\CAN\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ENQ\SOH\DC2\EOT\156\ETX\EM\RS\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ENQ\ETX\DC2\EOT\156\ETX,-\n\
\\f\n\
\\EOT\EOT\DC3\STX\ACK\DC2\EOT\157\ETX\EOT.\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ACK\EOT\DC2\EOT\157\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ACK\ENQ\DC2\EOT\157\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ACK\SOH\DC2\EOT\157\ETX\DC4\ESC\n\
\\r\n\
\\ENQ\EOT\DC3\STX\ACK\ETX\DC2\EOT\157\ETX,-\n\
\\145\SOH\n\
\\EOT\EOT\DC3\STX\a\DC2\EOT\162\ETX\EOTB\SUB\130\SOH If it's true, indicates to the client that it must\n\
\ always connect through the service url after the\n\
\ lookup has been completed.\n\
\\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\EOT\DC2\EOT\162\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\ENQ\DC2\EOT\162\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\SOH\DC2\EOT\162\ETX\DC2+\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\ETX\DC2\EOT\162\ETX./\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\b\DC2\EOT\162\ETX0A\n\
\\r\n\
\\ENQ\EOT\DC3\STX\a\a\DC2\EOT\162\ETX;@\n\
\\157\SOH\n\
\\STX\EOT\DC4\DC2\ACK\167\ETX\NUL\189\ETX\SOH\SUB\142\SOH/ Create a new Producer on a topic, assigning the given producer_id,\n\
\/ all messages sent with this producer_id will be persisted on the topic\n\
\\n\
\\v\n\
\\ETX\EOT\DC4\SOH\DC2\EOT\167\ETX\b\ETB\n\
\\f\n\
\\EOT\EOT\DC4\STX\NUL\DC2\EOT\168\ETX\EOT&\n\
\\r\n\
\\ENQ\EOT\DC4\STX\NUL\EOT\DC2\EOT\168\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\NUL\ENQ\DC2\EOT\168\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\NUL\SOH\DC2\EOT\168\ETX\DC4\EM\n\
\\r\n\
\\ENQ\EOT\DC4\STX\NUL\ETX\DC2\EOT\168\ETX$%\n\
\\f\n\
\\EOT\EOT\DC4\STX\SOH\DC2\EOT\169\ETX\EOT&\n\
\\r\n\
\\ENQ\EOT\DC4\STX\SOH\EOT\DC2\EOT\169\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\SOH\ENQ\DC2\EOT\169\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\SOH\SOH\DC2\EOT\169\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\DC4\STX\SOH\ETX\DC2\EOT\169\ETX$%\n\
\\f\n\
\\EOT\EOT\DC4\STX\STX\DC2\EOT\170\ETX\EOT&\n\
\\r\n\
\\ENQ\EOT\DC4\STX\STX\EOT\DC2\EOT\170\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\STX\ENQ\DC2\EOT\170\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\STX\SOH\DC2\EOT\170\ETX\DC4\RS\n\
\\r\n\
\\ENQ\EOT\DC4\STX\STX\ETX\DC2\EOT\170\ETX$%\n\
\{\n\
\\EOT\EOT\DC4\STX\ETX\DC2\EOT\174\ETX\EOT&\SUBm/ If a producer name is specified, the name will be used,\n\
\/ otherwise the broker will generate a unique name\n\
\\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ETX\EOT\DC2\EOT\174\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ETX\ENQ\DC2\EOT\174\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ETX\SOH\DC2\EOT\174\ETX\DC4!\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ETX\ETX\DC2\EOT\174\ETX$%\n\
\\f\n\
\\EOT\EOT\DC4\STX\EOT\DC2\EOT\176\ETX\EOT8\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\EOT\DC2\EOT\176\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\ENQ\DC2\EOT\176\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\SOH\DC2\EOT\176\ETX\DC2\ESC\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\ETX\DC2\EOT\176\ETX$%\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\b\DC2\EOT\176\ETX&7\n\
\\r\n\
\\ENQ\EOT\DC4\STX\EOT\a\DC2\EOT\176\ETX16\n\
\A\n\
\\EOT\EOT\DC4\STX\ENQ\DC2\EOT\179\ETX\EOT&\SUB3/ Add optional metadata key=value to this producer\n\
\\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ENQ\EOT\DC2\EOT\179\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ENQ\ACK\DC2\EOT\179\ETX\r\NAK\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ENQ\SOH\DC2\EOT\179\ETX\SYN\RS\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ENQ\ETX\DC2\EOT\179\ETX$%\n\
\\f\n\
\\EOT\EOT\DC4\STX\ACK\DC2\EOT\181\ETX\EOT\US\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ACK\EOT\DC2\EOT\181\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ACK\ACK\DC2\EOT\181\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ACK\SOH\DC2\EOT\181\ETX\DC4\SUB\n\
\\r\n\
\\ENQ\EOT\DC4\STX\ACK\ETX\DC2\EOT\181\ETX\GS\RS\n\
\S\n\
\\EOT\EOT\DC4\STX\a\DC2\EOT\184\ETX\EOT,\SUBE If producer reconnect to broker, the epoch of this producer will +1\n\
\\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\EOT\DC2\EOT\184\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\ENQ\DC2\EOT\184\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\SOH\DC2\EOT\184\ETX\DC4\EM\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\ETX\DC2\EOT\184\ETX\FS\GS\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\b\DC2\EOT\184\ETX\RS+\n\
\\r\n\
\\ENQ\EOT\DC4\STX\a\a\DC2\EOT\184\ETX)*\n\
\\156\SOH\n\
\\EOT\EOT\DC4\STX\b\DC2\EOT\188\ETX\EOTC\SUB\141\SOH Indicate the name of the producer is generated or user provided\n\
\ Use default true here is in order to be forward compatible with the client\n\
\\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\EOT\DC2\EOT\188\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\ENQ\DC2\EOT\188\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\SOH\DC2\EOT\188\ETX\DC2-\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\ETX\DC2\EOT\188\ETX01\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\b\DC2\EOT\188\ETX2B\n\
\\r\n\
\\ENQ\EOT\DC4\STX\b\a\DC2\EOT\188\ETX=A\n\
\\f\n\
\\STX\EOT\NAK\DC2\ACK\191\ETX\NUL\201\ETX\SOH\n\
\\v\n\
\\ETX\EOT\NAK\SOH\DC2\EOT\191\ETX\b\DC3\n\
\\f\n\
\\EOT\EOT\NAK\STX\NUL\DC2\EOT\192\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\NAK\STX\NUL\EOT\DC2\EOT\192\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\NUL\ENQ\DC2\EOT\192\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\NUL\SOH\DC2\EOT\192\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\NAK\STX\NUL\ETX\DC2\EOT\192\ETX\"#\n\
\\f\n\
\\EOT\EOT\NAK\STX\SOH\DC2\EOT\193\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\NAK\STX\SOH\EOT\DC2\EOT\193\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\SOH\ENQ\DC2\EOT\193\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\SOH\SOH\DC2\EOT\193\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\NAK\STX\SOH\ETX\DC2\EOT\193\ETX\"#\n\
\\f\n\
\\EOT\EOT\NAK\STX\STX\DC2\EOT\194\ETX\EOT2\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\EOT\DC2\EOT\194\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\ENQ\DC2\EOT\194\ETX\r\DC2\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\SOH\DC2\EOT\194\ETX\DC3\US\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\ETX\DC2\EOT\194\ETX\"#\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\b\DC2\EOT\194\ETX$1\n\
\\r\n\
\\ENQ\EOT\NAK\STX\STX\a\DC2\EOT\194\ETX/0\n\
\\f\n\
\\EOT\EOT\NAK\STX\ETX\DC2\EOT\195\ETX\EOT7\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\EOT\DC2\EOT\195\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\ENQ\DC2\EOT\195\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\SOH\DC2\EOT\195\ETX\DC4$\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\ETX\DC2\EOT\195\ETX'(\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\b\DC2\EOT\195\ETX)6\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ETX\a\DC2\EOT\195\ETX45\n\
\\f\n\
\\EOT\EOT\NAK\STX\EOT\DC2\EOT\196\ETX\EOT6\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\EOT\DC2\EOT\196\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\ENQ\DC2\EOT\196\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\SOH\DC2\EOT\196\ETX\DC4#\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\ETX\DC2\EOT\196\ETX&'\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\b\DC2\EOT\196\ETX(5\n\
\\r\n\
\\ENQ\EOT\NAK\STX\EOT\a\DC2\EOT\196\ETX34\n\
\[\n\
\\EOT\EOT\NAK\STX\ENQ\DC2\EOT\199\ETX\EOT:\SUBM/ Add highest sequence id to support batch message with external sequence id\n\
\\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\EOT\DC2\EOT\199\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\ENQ\DC2\EOT\199\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\SOH\DC2\EOT\199\ETX\DC4'\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\ETX\DC2\EOT\199\ETX*+\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\b\DC2\EOT\199\ETX,9\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ENQ\a\DC2\EOT\199\ETX78\n\
\\f\n\
\\EOT\EOT\NAK\STX\ACK\DC2\EOT\200\ETX\EOT4\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\EOT\DC2\EOT\200\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\ENQ\DC2\EOT\200\ETX\r\DC1\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\SOH\DC2\EOT\200\ETX\DC2\SUB\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\ETX\DC2\EOT\200\ETX !\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\b\DC2\EOT\200\ETX\"3\n\
\\r\n\
\\ENQ\EOT\NAK\STX\ACK\a\DC2\EOT\200\ETX-2\n\
\\f\n\
\\STX\EOT\SYN\DC2\ACK\203\ETX\NUL\208\ETX\SOH\n\
\\v\n\
\\ETX\EOT\SYN\SOH\DC2\EOT\203\ETX\b\SUB\n\
\\f\n\
\\EOT\EOT\SYN\STX\NUL\DC2\EOT\204\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\SYN\STX\NUL\EOT\DC2\EOT\204\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SYN\STX\NUL\ENQ\DC2\EOT\204\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SYN\STX\NUL\SOH\DC2\EOT\204\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\SYN\STX\NUL\ETX\DC2\EOT\204\ETX\"#\n\
\\f\n\
\\EOT\EOT\SYN\STX\SOH\DC2\EOT\205\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\SYN\STX\SOH\EOT\DC2\EOT\205\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SYN\STX\SOH\ENQ\DC2\EOT\205\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SYN\STX\SOH\SOH\DC2\EOT\205\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\SYN\STX\SOH\ETX\DC2\EOT\205\ETX\"#\n\
\\f\n\
\\EOT\EOT\SYN\STX\STX\DC2\EOT\206\ETX\EOT*\n\
\\r\n\
\\ENQ\EOT\SYN\STX\STX\EOT\DC2\EOT\206\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SYN\STX\STX\ACK\DC2\EOT\206\ETX\r\SUB\n\
\\r\n\
\\ENQ\EOT\SYN\STX\STX\SOH\DC2\EOT\206\ETX\ESC%\n\
\\r\n\
\\ENQ\EOT\SYN\STX\STX\ETX\DC2\EOT\206\ETX()\n\
\\f\n\
\\EOT\EOT\SYN\STX\ETX\DC2\EOT\207\ETX\EOT:\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\EOT\DC2\EOT\207\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\ENQ\DC2\EOT\207\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\SOH\DC2\EOT\207\ETX\DC4'\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\ETX\DC2\EOT\207\ETX*+\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\b\DC2\EOT\207\ETX,9\n\
\\r\n\
\\ENQ\EOT\SYN\STX\ETX\a\DC2\EOT\207\ETX78\n\
\\f\n\
\\STX\EOT\ETB\DC2\ACK\210\ETX\NUL\215\ETX\SOH\n\
\\v\n\
\\ETX\EOT\ETB\SOH\DC2\EOT\210\ETX\b\CAN\n\
\\f\n\
\\EOT\EOT\ETB\STX\NUL\DC2\EOT\211\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\ETB\STX\NUL\EOT\DC2\EOT\211\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\ETB\STX\NUL\ENQ\DC2\EOT\211\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\ETB\STX\NUL\SOH\DC2\EOT\211\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\ETB\STX\NUL\ETX\DC2\EOT\211\ETX\"#\n\
\\f\n\
\\EOT\EOT\ETB\STX\SOH\DC2\EOT\212\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\ETB\STX\SOH\EOT\DC2\EOT\212\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\ETB\STX\SOH\ENQ\DC2\EOT\212\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\ETB\STX\SOH\SOH\DC2\EOT\212\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\ETB\STX\SOH\ETX\DC2\EOT\212\ETX\"#\n\
\\f\n\
\\EOT\EOT\ETB\STX\STX\DC2\EOT\213\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\ETB\STX\STX\EOT\DC2\EOT\213\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\ETB\STX\STX\ACK\DC2\EOT\213\ETX\r\CAN\n\
\\r\n\
\\ENQ\EOT\ETB\STX\STX\SOH\DC2\EOT\213\ETX\EM\RS\n\
\\r\n\
\\ENQ\EOT\ETB\STX\STX\ETX\DC2\EOT\213\ETX\"#\n\
\\f\n\
\\EOT\EOT\ETB\STX\ETX\DC2\EOT\214\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\ETB\STX\ETX\EOT\DC2\EOT\214\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\ETB\STX\ETX\ENQ\DC2\EOT\214\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\ETB\STX\ETX\SOH\DC2\EOT\214\ETX\DC4\ESC\n\
\\r\n\
\\ENQ\EOT\ETB\STX\ETX\ETX\DC2\EOT\214\ETX\"#\n\
\\f\n\
\\STX\EOT\CAN\DC2\ACK\217\ETX\NUL\222\ETX\SOH\n\
\\v\n\
\\ETX\EOT\CAN\SOH\DC2\EOT\217\ETX\b\SYN\n\
\\f\n\
\\EOT\EOT\CAN\STX\NUL\DC2\EOT\218\ETX\EOT*\n\
\\r\n\
\\ENQ\EOT\CAN\STX\NUL\EOT\DC2\EOT\218\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\CAN\STX\NUL\ENQ\DC2\EOT\218\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\CAN\STX\NUL\SOH\DC2\EOT\218\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\CAN\STX\NUL\ETX\DC2\EOT\218\ETX()\n\
\\f\n\
\\EOT\EOT\CAN\STX\SOH\DC2\EOT\219\ETX\EOT*\n\
\\r\n\
\\ENQ\EOT\CAN\STX\SOH\EOT\DC2\EOT\219\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\CAN\STX\SOH\ACK\DC2\EOT\219\ETX\r\SUB\n\
\\r\n\
\\ENQ\EOT\CAN\STX\SOH\SOH\DC2\EOT\219\ETX\ESC%\n\
\\r\n\
\\ENQ\EOT\CAN\STX\SOH\ETX\DC2\EOT\219\ETX()\n\
\\f\n\
\\EOT\EOT\CAN\STX\STX\DC2\EOT\220\ETX\EOT8\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\EOT\DC2\EOT\220\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\ENQ\DC2\EOT\220\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\SOH\DC2\EOT\220\ETX\DC4$\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\ETX\DC2\EOT\220\ETX()\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\b\DC2\EOT\220\ETX*7\n\
\\r\n\
\\ENQ\EOT\CAN\STX\STX\a\DC2\EOT\220\ETX56\n\
\\f\n\
\\EOT\EOT\CAN\STX\ETX\DC2\EOT\221\ETX\EOT\US\n\
\\r\n\
\\ENQ\EOT\CAN\STX\ETX\EOT\DC2\EOT\221\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\CAN\STX\ETX\ENQ\DC2\EOT\221\ETX\r\DC2\n\
\\r\n\
\\ENQ\EOT\CAN\STX\ETX\SOH\DC2\EOT\221\ETX\DC3\SUB\n\
\\r\n\
\\ENQ\EOT\CAN\STX\ETX\ETX\DC2\EOT\221\ETX\GS\RS\n\
\\f\n\
\\STX\EOT\EM\DC2\ACK\224\ETX\NUL\252\ETX\SOH\n\
\\v\n\
\\ETX\EOT\EM\SOH\DC2\EOT\224\ETX\b\DC2\n\
\\SO\n\
\\EOT\EOT\EM\EOT\NUL\DC2\ACK\225\ETX\EOT\228\ETX\ENQ\n\
\\r\n\
\\ENQ\EOT\EM\EOT\NUL\SOH\DC2\EOT\225\ETX\t\DLE\n\
\\SO\n\
\\ACK\EOT\EM\EOT\NUL\STX\NUL\DC2\EOT\226\ETX\b\ETB\n\
\\SI\n\
\\a\EOT\EM\EOT\NUL\STX\NUL\SOH\DC2\EOT\226\ETX\b\DC2\n\
\\SI\n\
\\a\EOT\EM\EOT\NUL\STX\NUL\STX\DC2\EOT\226\ETX\NAK\SYN\n\
\\SO\n\
\\ACK\EOT\EM\EOT\NUL\STX\SOH\DC2\EOT\227\ETX\b\ETB\n\
\\SI\n\
\\a\EOT\EM\EOT\NUL\STX\SOH\SOH\DC2\EOT\227\ETX\b\DC2\n\
\\SI\n\
\\a\EOT\EM\EOT\NUL\STX\SOH\STX\DC2\EOT\227\ETX\NAK\SYN\n\
\\f\n\
\\EOT\EOT\EM\STX\NUL\DC2\EOT\230\ETX\EOT*\n\
\\r\n\
\\ENQ\EOT\EM\STX\NUL\EOT\DC2\EOT\230\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\NUL\ENQ\DC2\EOT\230\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\EM\STX\NUL\SOH\DC2\EOT\230\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\EM\STX\NUL\ETX\DC2\EOT\230\ETX()\n\
\\f\n\
\\EOT\EOT\EM\STX\SOH\DC2\EOT\231\ETX\EOT*\n\
\\r\n\
\\ENQ\EOT\EM\STX\SOH\EOT\DC2\EOT\231\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\SOH\ACK\DC2\EOT\231\ETX\r\DC4\n\
\\r\n\
\\ENQ\EOT\EM\STX\SOH\SOH\DC2\EOT\231\ETX\NAK\GS\n\
\\r\n\
\\ENQ\EOT\EM\STX\SOH\ETX\DC2\EOT\231\ETX()\n\
\U\n\
\\EOT\EOT\EM\STX\STX\DC2\EOT\234\ETX\EOT*\SUBG In case of individual acks, the client can pass a list of message ids\n\
\\n\
\\r\n\
\\ENQ\EOT\EM\STX\STX\EOT\DC2\EOT\234\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\STX\ACK\DC2\EOT\234\ETX\r\SUB\n\
\\r\n\
\\ENQ\EOT\EM\STX\STX\SOH\DC2\EOT\234\ETX\ESC%\n\
\\r\n\
\\ENQ\EOT\EM\STX\STX\ETX\DC2\EOT\234\ETX()\n\
\\159\SOH\n\
\\EOT\EOT\EM\EOT\SOH\DC2\ACK\239\ETX\EOT\245\ETX\ENQ\SUB\142\SOH Acks can contain a flag to indicate the consumer\n\
\ received an invalid message that got discarded\n\
\ before being passed on to the application.\n\
\\n\
\\r\n\
\\ENQ\EOT\EM\EOT\SOH\SOH\DC2\EOT\239\ETX\t\CAN\n\
\\SO\n\
\\ACK\EOT\EM\EOT\SOH\STX\NUL\DC2\EOT\240\ETX\b'\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\NUL\SOH\DC2\EOT\240\ETX\b\"\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\NUL\STX\DC2\EOT\240\ETX%&\n\
\\SO\n\
\\ACK\EOT\EM\EOT\SOH\STX\SOH\DC2\EOT\241\ETX\b\US\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\SOH\SOH\DC2\EOT\241\ETX\b\SUB\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\SOH\STX\DC2\EOT\241\ETX\GS\RS\n\
\\SO\n\
\\ACK\EOT\EM\EOT\SOH\STX\STX\DC2\EOT\242\ETX\b\GS\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\STX\SOH\DC2\EOT\242\ETX\b\CAN\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\STX\STX\DC2\EOT\242\ETX\ESC\FS\n\
\\SO\n\
\\ACK\EOT\EM\EOT\SOH\STX\ETX\DC2\EOT\243\ETX\b\"\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\ETX\SOH\DC2\EOT\243\ETX\b\GS\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\ETX\STX\DC2\EOT\243\ETX !\n\
\\SO\n\
\\ACK\EOT\EM\EOT\SOH\STX\EOT\DC2\EOT\244\ETX\b\FS\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\EOT\SOH\DC2\EOT\244\ETX\b\ETB\n\
\\SI\n\
\\a\EOT\EM\EOT\SOH\STX\EOT\STX\DC2\EOT\244\ETX\SUB\ESC\n\
\\f\n\
\\EOT\EOT\EM\STX\ETX\DC2\EOT\247\ETX\EOT2\n\
\\r\n\
\\ENQ\EOT\EM\STX\ETX\EOT\DC2\EOT\247\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\ETX\ACK\DC2\EOT\247\ETX\r\FS\n\
\\r\n\
\\ENQ\EOT\EM\STX\ETX\SOH\DC2\EOT\247\ETX\GS-\n\
\\r\n\
\\ENQ\EOT\EM\STX\ETX\ETX\DC2\EOT\247\ETX01\n\
\\f\n\
\\EOT\EOT\EM\STX\EOT\DC2\EOT\248\ETX\EOT)\n\
\\r\n\
\\ENQ\EOT\EM\STX\EOT\EOT\DC2\EOT\248\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\EOT\ACK\DC2\EOT\248\ETX\r\EM\n\
\\r\n\
\\ENQ\EOT\EM\STX\EOT\SOH\DC2\EOT\248\ETX\SUB$\n\
\\r\n\
\\ENQ\EOT\EM\STX\EOT\ETX\DC2\EOT\248\ETX'(\n\
\\f\n\
\\EOT\EOT\EM\STX\ENQ\DC2\EOT\250\ETX\EOT7\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\EOT\DC2\EOT\250\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\ENQ\DC2\EOT\250\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\SOH\DC2\EOT\250\ETX\DC4$\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\ETX\DC2\EOT\250\ETX'(\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\b\DC2\EOT\250\ETX)6\n\
\\r\n\
\\ENQ\EOT\EM\STX\ENQ\a\DC2\EOT\250\ETX45\n\
\\f\n\
\\EOT\EOT\EM\STX\ACK\DC2\EOT\251\ETX\EOT6\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\EOT\DC2\EOT\251\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\ENQ\DC2\EOT\251\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\SOH\DC2\EOT\251\ETX\DC4#\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\ETX\DC2\EOT\251\ETX&'\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\b\DC2\EOT\251\ETX(5\n\
\\r\n\
\\ENQ\EOT\EM\STX\ACK\a\DC2\EOT\251\ETX34\n\
\\f\n\
\\STX\EOT\SUB\DC2\ACK\254\ETX\NUL\132\EOT\SOH\n\
\\v\n\
\\ETX\EOT\SUB\SOH\DC2\EOT\254\ETX\b\SUB\n\
\\f\n\
\\EOT\EOT\SUB\STX\NUL\DC2\EOT\255\ETX\EOT$\n\
\\r\n\
\\ENQ\EOT\SUB\STX\NUL\EOT\DC2\EOT\255\ETX\EOT\f\n\
\\r\n\
\\ENQ\EOT\SUB\STX\NUL\ENQ\DC2\EOT\255\ETX\r\DC3\n\
\\r\n\
\\ENQ\EOT\SUB\STX\NUL\SOH\DC2\EOT\255\ETX\DC4\US\n\
\\r\n\
\\ENQ\EOT\SUB\STX\NUL\ETX\DC2\EOT\255\ETX\"#\n\
\\f\n\
\\EOT\EOT\SUB\STX\SOH\DC2\EOT\128\EOT\EOT8\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\EOT\DC2\EOT\128\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\ENQ\DC2\EOT\128\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\SOH\DC2\EOT\128\EOT\DC4$\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\ETX\DC2\EOT\128\EOT()\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\b\DC2\EOT\128\EOT*7\n\
\\r\n\
\\ENQ\EOT\SUB\STX\SOH\a\DC2\EOT\128\EOT56\n\
\\f\n\
\\EOT\EOT\SUB\STX\STX\DC2\EOT\129\EOT\EOT6\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\EOT\DC2\EOT\129\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\ENQ\DC2\EOT\129\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\SOH\DC2\EOT\129\EOT\DC4#\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\ETX\DC2\EOT\129\EOT&'\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\b\DC2\EOT\129\EOT(5\n\
\\r\n\
\\ENQ\EOT\SUB\STX\STX\a\DC2\EOT\129\EOT34\n\
\\f\n\
\\EOT\EOT\SUB\STX\ETX\DC2\EOT\130\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT\SUB\STX\ETX\EOT\DC2\EOT\130\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\SUB\STX\ETX\ACK\DC2\EOT\130\EOT\r\CAN\n\
\\r\n\
\\ENQ\EOT\SUB\STX\ETX\SOH\DC2\EOT\130\EOT\EM\RS\n\
\\r\n\
\\ENQ\EOT\SUB\STX\ETX\ETX\DC2\EOT\130\EOT!\"\n\
\\f\n\
\\EOT\EOT\SUB\STX\EOT\DC2\EOT\131\EOT\EOT \n\
\\r\n\
\\ENQ\EOT\SUB\STX\EOT\EOT\DC2\EOT\131\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\SUB\STX\EOT\ENQ\DC2\EOT\131\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\SUB\STX\EOT\SOH\DC2\EOT\131\EOT\DC4\ESC\n\
\\r\n\
\\ENQ\EOT\SUB\STX\EOT\ETX\DC2\EOT\131\EOT\RS\US\n\
\*\n\
\\STX\EOT\ESC\DC2\ACK\135\EOT\NUL\138\EOT\SOH\SUB\FS changes on active consumer\n\
\\n\
\\v\n\
\\ETX\EOT\ESC\SOH\DC2\EOT\135\EOT\b#\n\
\\f\n\
\\EOT\EOT\ESC\STX\NUL\DC2\EOT\136\EOT\b+\n\
\\r\n\
\\ENQ\EOT\ESC\STX\NUL\EOT\DC2\EOT\136\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT\ESC\STX\NUL\ENQ\DC2\EOT\136\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT\ESC\STX\NUL\SOH\DC2\EOT\136\EOT\CAN#\n\
\\r\n\
\\ENQ\EOT\ESC\STX\NUL\ETX\DC2\EOT\136\EOT)*\n\
\\f\n\
\\EOT\EOT\ESC\STX\SOH\DC2\EOT\137\EOT\b:\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\EOT\DC2\EOT\137\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\ENQ\DC2\EOT\137\EOT\DC1\NAK\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\SOH\DC2\EOT\137\EOT\SYN\US\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\ETX\DC2\EOT\137\EOT&'\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\b\DC2\EOT\137\EOT(9\n\
\\r\n\
\\ENQ\EOT\ESC\STX\SOH\a\DC2\EOT\137\EOT38\n\
\\f\n\
\\STX\EOT\FS\DC2\ACK\140\EOT\NUL\146\EOT\SOH\n\
\\v\n\
\\ETX\EOT\FS\SOH\DC2\EOT\140\EOT\b\DC3\n\
\\f\n\
\\EOT\EOT\FS\STX\NUL\DC2\EOT\141\EOT\EOT*\n\
\\r\n\
\\ENQ\EOT\FS\STX\NUL\EOT\DC2\EOT\141\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\FS\STX\NUL\ENQ\DC2\EOT\141\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\FS\STX\NUL\SOH\DC2\EOT\141\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT\FS\STX\NUL\ETX\DC2\EOT\141\EOT()\n\
\c\n\
\\EOT\EOT\FS\STX\SOH\DC2\EOT\145\EOT\EOT+\SUBU Max number of messages to prefetch, in addition\n\
\ of any number previously specified\n\
\\n\
\\r\n\
\\ENQ\EOT\FS\STX\SOH\EOT\DC2\EOT\145\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\FS\STX\SOH\ENQ\DC2\EOT\145\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\FS\STX\SOH\SOH\DC2\EOT\145\EOT\DC4\"\n\
\\r\n\
\\ENQ\EOT\FS\STX\SOH\ETX\DC2\EOT\145\EOT)*\n\
\\f\n\
\\STX\EOT\GS\DC2\ACK\148\EOT\NUL\151\EOT\SOH\n\
\\v\n\
\\ETX\EOT\GS\SOH\DC2\EOT\148\EOT\b\SUB\n\
\\f\n\
\\EOT\EOT\GS\STX\NUL\DC2\EOT\149\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\GS\STX\NUL\EOT\DC2\EOT\149\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\GS\STX\NUL\ENQ\DC2\EOT\149\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\GS\STX\NUL\SOH\DC2\EOT\149\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT\GS\STX\NUL\ETX\DC2\EOT\149\EOT\"#\n\
\\f\n\
\\EOT\EOT\GS\STX\SOH\DC2\EOT\150\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\GS\STX\SOH\EOT\DC2\EOT\150\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\GS\STX\SOH\ENQ\DC2\EOT\150\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\GS\STX\SOH\SOH\DC2\EOT\150\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT\GS\STX\SOH\ETX\DC2\EOT\150\EOT\"#\n\
\E\n\
\\STX\EOT\RS\DC2\ACK\154\EOT\NUL\160\EOT\SOH\SUB7 Reset an existing consumer to a particular message id\n\
\\n\
\\v\n\
\\ETX\EOT\RS\SOH\DC2\EOT\154\EOT\b\DC3\n\
\\f\n\
\\EOT\EOT\RS\STX\NUL\DC2\EOT\155\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\RS\STX\NUL\EOT\DC2\EOT\155\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\RS\STX\NUL\ENQ\DC2\EOT\155\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\RS\STX\NUL\SOH\DC2\EOT\155\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT\RS\STX\NUL\ETX\DC2\EOT\155\EOT\"#\n\
\\f\n\
\\EOT\EOT\RS\STX\SOH\DC2\EOT\156\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\RS\STX\SOH\EOT\DC2\EOT\156\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\RS\STX\SOH\ENQ\DC2\EOT\156\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\RS\STX\SOH\SOH\DC2\EOT\156\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT\RS\STX\SOH\ETX\DC2\EOT\156\EOT\"#\n\
\\f\n\
\\EOT\EOT\RS\STX\STX\DC2\EOT\158\EOT\EOT*\n\
\\r\n\
\\ENQ\EOT\RS\STX\STX\EOT\DC2\EOT\158\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\RS\STX\STX\ACK\DC2\EOT\158\EOT\r\SUB\n\
\\r\n\
\\ENQ\EOT\RS\STX\STX\SOH\DC2\EOT\158\EOT\ESC%\n\
\\r\n\
\\ENQ\EOT\RS\STX\STX\ETX\DC2\EOT\158\EOT()\n\
\\f\n\
\\EOT\EOT\RS\STX\ETX\DC2\EOT\159\EOT\EOT-\n\
\\r\n\
\\ENQ\EOT\RS\STX\ETX\EOT\DC2\EOT\159\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\RS\STX\ETX\ENQ\DC2\EOT\159\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\RS\STX\ETX\SOH\DC2\EOT\159\EOT\DC4(\n\
\\r\n\
\\ENQ\EOT\RS\STX\ETX\ETX\DC2\EOT\159\EOT+,\n\
\\141\SOH\n\
\\STX\EOT\US\DC2\ACK\165\EOT\NUL\167\EOT\SOH\SUB\DEL Message sent by broker to client when a topic\n\
\ has been forcefully terminated and there are no more\n\
\ messages left to consume\n\
\\n\
\\v\n\
\\ETX\EOT\US\SOH\DC2\EOT\165\EOT\b \n\
\\f\n\
\\EOT\EOT\US\STX\NUL\DC2\EOT\166\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\US\STX\NUL\EOT\DC2\EOT\166\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\US\STX\NUL\ENQ\DC2\EOT\166\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\US\STX\NUL\SOH\DC2\EOT\166\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT\US\STX\NUL\ETX\DC2\EOT\166\EOT\"#\n\
\\f\n\
\\STX\EOT \DC2\ACK\169\EOT\NUL\172\EOT\SOH\n\
\\v\n\
\\ETX\EOT \SOH\DC2\EOT\169\EOT\b\FS\n\
\\f\n\
\\EOT\EOT \STX\NUL\DC2\EOT\170\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT \STX\NUL\EOT\DC2\EOT\170\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT \STX\NUL\ENQ\DC2\EOT\170\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT \STX\NUL\SOH\DC2\EOT\170\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT \STX\NUL\ETX\DC2\EOT\170\EOT\"#\n\
\\f\n\
\\EOT\EOT \STX\SOH\DC2\EOT\171\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT \STX\SOH\EOT\DC2\EOT\171\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT \STX\SOH\ENQ\DC2\EOT\171\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT \STX\SOH\SOH\DC2\EOT\171\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT \STX\SOH\ETX\DC2\EOT\171\EOT!\"\n\
\\f\n\
\\STX\EOT!\DC2\ACK\174\EOT\NUL\177\EOT\SOH\n\
\\v\n\
\\ETX\EOT!\SOH\DC2\EOT\174\EOT\b\FS\n\
\\f\n\
\\EOT\EOT!\STX\NUL\DC2\EOT\175\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT!\STX\NUL\EOT\DC2\EOT\175\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT!\STX\NUL\ENQ\DC2\EOT\175\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT!\STX\NUL\SOH\DC2\EOT\175\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT!\STX\NUL\ETX\DC2\EOT\175\EOT\"#\n\
\\f\n\
\\EOT\EOT!\STX\SOH\DC2\EOT\176\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT!\STX\SOH\EOT\DC2\EOT\176\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT!\STX\SOH\ENQ\DC2\EOT\176\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT!\STX\SOH\SOH\DC2\EOT\176\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT!\STX\SOH\ETX\DC2\EOT\176\EOT!\"\n\
\\f\n\
\\STX\EOT\"\DC2\ACK\179\EOT\NUL\182\EOT\SOH\n\
\\v\n\
\\ETX\EOT\"\SOH\DC2\EOT\179\EOT\b.\n\
\\f\n\
\\EOT\EOT\"\STX\NUL\DC2\EOT\180\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT\"\STX\NUL\EOT\DC2\EOT\180\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\"\STX\NUL\ENQ\DC2\EOT\180\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT\"\STX\NUL\SOH\DC2\EOT\180\EOT\DC4\US\n\
\\r\n\
\\ENQ\EOT\"\STX\NUL\ETX\DC2\EOT\180\EOT\"#\n\
\\f\n\
\\EOT\EOT\"\STX\SOH\DC2\EOT\181\EOT\EOT+\n\
\\r\n\
\\ENQ\EOT\"\STX\SOH\EOT\DC2\EOT\181\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT\"\STX\SOH\ACK\DC2\EOT\181\EOT\r\SUB\n\
\\r\n\
\\ENQ\EOT\"\STX\SOH\SOH\DC2\EOT\181\EOT\ESC&\n\
\\r\n\
\\ENQ\EOT\"\STX\SOH\ETX\DC2\EOT\181\EOT)*\n\
\\f\n\
\\STX\EOT#\DC2\ACK\184\EOT\NUL\187\EOT\SOH\n\
\\v\n\
\\ETX\EOT#\SOH\DC2\EOT\184\EOT\b\SYN\n\
\\f\n\
\\EOT\EOT#\STX\NUL\DC2\EOT\185\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT#\STX\NUL\EOT\DC2\EOT\185\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT#\STX\NUL\ENQ\DC2\EOT\185\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT#\STX\NUL\SOH\DC2\EOT\185\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT#\STX\NUL\ETX\DC2\EOT\185\EOT!\"\n\
\\f\n\
\\EOT\EOT#\STX\SOH\DC2\EOT\186\EOT\EOT\US\n\
\\r\n\
\\ENQ\EOT#\STX\SOH\EOT\DC2\EOT\186\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT#\STX\SOH\ACK\DC2\EOT\186\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT#\STX\SOH\SOH\DC2\EOT\186\EOT\DC4\SUB\n\
\\r\n\
\\ENQ\EOT#\STX\SOH\ETX\DC2\EOT\186\EOT\GS\RS\n\
\.\n\
\\STX\EOT$\DC2\ACK\190\EOT\NUL\198\EOT\SOH\SUB / Response from CommandProducer\n\
\\n\
\\v\n\
\\ETX\EOT$\SOH\DC2\EOT\190\EOT\b\RS\n\
\\f\n\
\\EOT\EOT$\STX\NUL\DC2\EOT\191\EOT\EOT&\n\
\\r\n\
\\ENQ\EOT$\STX\NUL\EOT\DC2\EOT\191\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT$\STX\NUL\ENQ\DC2\EOT\191\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT$\STX\NUL\SOH\DC2\EOT\191\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT$\STX\NUL\ETX\DC2\EOT\191\EOT$%\n\
\\f\n\
\\EOT\EOT$\STX\SOH\DC2\EOT\192\EOT\EOT&\n\
\\r\n\
\\ENQ\EOT$\STX\SOH\EOT\DC2\EOT\192\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT$\STX\SOH\ENQ\DC2\EOT\192\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT$\STX\SOH\SOH\DC2\EOT\192\EOT\DC4!\n\
\\r\n\
\\ENQ\EOT$\STX\SOH\ETX\DC2\EOT\192\EOT$%\n\
\\159\SOH\n\
\\EOT\EOT$\STX\STX\DC2\EOT\196\EOT\EOT8\SUB\144\SOH The last sequence id that was stored by this producer in the previous session\n\
\ This will only be meaningful if deduplication has been enabled.\n\
\\n\
\\r\n\
\\ENQ\EOT$\STX\STX\EOT\DC2\EOT\196\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT$\STX\STX\ENQ\DC2\EOT\196\EOT\r\DC2\n\
\\r\n\
\\ENQ\EOT$\STX\STX\SOH\DC2\EOT\196\EOT\DC4$\n\
\\r\n\
\\ENQ\EOT$\STX\STX\ETX\DC2\EOT\196\EOT'(\n\
\\r\n\
\\ENQ\EOT$\STX\STX\b\DC2\EOT\196\EOT)7\n\
\\r\n\
\\ENQ\EOT$\STX\STX\a\DC2\EOT\196\EOT46\n\
\\f\n\
\\EOT\EOT$\STX\ETX\DC2\EOT\197\EOT\EOT&\n\
\\r\n\
\\ENQ\EOT$\STX\ETX\EOT\DC2\EOT\197\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT$\STX\ETX\ENQ\DC2\EOT\197\EOT\r\DC2\n\
\\r\n\
\\ENQ\EOT$\STX\ETX\SOH\DC2\EOT\197\EOT\DC3!\n\
\\r\n\
\\ENQ\EOT$\STX\ETX\ETX\DC2\EOT\197\EOT$%\n\
\\f\n\
\\STX\EOT%\DC2\ACK\200\EOT\NUL\204\EOT\SOH\n\
\\v\n\
\\ETX\EOT%\SOH\DC2\EOT\200\EOT\b\DC4\n\
\\f\n\
\\EOT\EOT%\STX\NUL\DC2\EOT\201\EOT\EOT$\n\
\\r\n\
\\ENQ\EOT%\STX\NUL\EOT\DC2\EOT\201\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT%\STX\NUL\ENQ\DC2\EOT\201\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT%\STX\NUL\SOH\DC2\EOT\201\EOT\DC4\RS\n\
\\r\n\
\\ENQ\EOT%\STX\NUL\ETX\DC2\EOT\201\EOT\"#\n\
\\f\n\
\\EOT\EOT%\STX\SOH\DC2\EOT\202\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT%\STX\SOH\EOT\DC2\EOT\202\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT%\STX\SOH\ACK\DC2\EOT\202\EOT\r\CAN\n\
\\r\n\
\\ENQ\EOT%\STX\SOH\SOH\DC2\EOT\202\EOT\EM\RS\n\
\\r\n\
\\ENQ\EOT%\STX\SOH\ETX\DC2\EOT\202\EOT!\"\n\
\\f\n\
\\EOT\EOT%\STX\STX\DC2\EOT\203\EOT\EOT#\n\
\\r\n\
\\ENQ\EOT%\STX\STX\EOT\DC2\EOT\203\EOT\EOT\f\n\
\\r\n\
\\ENQ\EOT%\STX\STX\ENQ\DC2\EOT\203\EOT\r\DC3\n\
\\r\n\
\\ENQ\EOT%\STX\STX\SOH\DC2\EOT\203\EOT\DC4\ESC\n\
\\r\n\
\\ENQ\EOT%\STX\STX\ETX\DC2\EOT\203\EOT!\"\n\
\\172\SOH\n\
\\STX\EOT&\DC2\ACK\209\EOT\NUL\210\EOT\SOH\SUB\157\SOH Commands to probe the state of connection.\n\
\ When either client or broker doesn't receive commands for certain\n\
\ amount of time, they will send a Ping probe.\n\
\\n\
\\v\n\
\\ETX\EOT&\SOH\DC2\EOT\209\EOT\b\DC3\n\
\\f\n\
\\STX\EOT'\DC2\ACK\211\EOT\NUL\212\EOT\SOH\n\
\\v\n\
\\ETX\EOT'\SOH\DC2\EOT\211\EOT\b\DC3\n\
\\f\n\
\\STX\EOT(\DC2\ACK\214\EOT\NUL\219\EOT\SOH\n\
\\v\n\
\\ETX\EOT(\SOH\DC2\EOT\214\EOT\b\FS\n\
\\f\n\
\\EOT\EOT(\STX\NUL\DC2\EOT\215\EOT\b/\n\
\\r\n\
\\ENQ\EOT(\STX\NUL\EOT\DC2\EOT\215\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT(\STX\NUL\ENQ\DC2\EOT\215\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT(\STX\NUL\SOH\DC2\EOT\215\EOT\CAN\"\n\
\\r\n\
\\ENQ\EOT(\STX\NUL\ETX\DC2\EOT\215\EOT-.\n\
\`\n\
\\EOT\EOT(\STX\SOH\DC2\EOT\218\EOT\b/\SUBR required string topic_name = 2;\n\
\ required string subscription_name = 3;\n\
\\n\
\\r\n\
\\ENQ\EOT(\STX\SOH\EOT\DC2\EOT\218\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT(\STX\SOH\ENQ\DC2\EOT\218\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT(\STX\SOH\SOH\DC2\EOT\218\EOT\CAN#\n\
\\r\n\
\\ENQ\EOT(\STX\SOH\ETX\DC2\EOT\218\EOT-.\n\
\\f\n\
\\STX\EOT)\DC2\ACK\221\EOT\NUL\133\ENQ\SOH\n\
\\v\n\
\\ETX\EOT)\SOH\DC2\EOT\221\EOT\b$\n\
\\f\n\
\\EOT\EOT)\STX\NUL\DC2\EOT\222\EOT\b4\n\
\\r\n\
\\ENQ\EOT)\STX\NUL\EOT\DC2\EOT\222\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\NUL\ENQ\DC2\EOT\222\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\NUL\SOH\DC2\EOT\222\EOT\CAN\"\n\
\\r\n\
\\ENQ\EOT)\STX\NUL\ETX\DC2\EOT\222\EOT23\n\
\\f\n\
\\EOT\EOT)\STX\SOH\DC2\EOT\223\EOT\b4\n\
\\r\n\
\\ENQ\EOT)\STX\SOH\EOT\DC2\EOT\223\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\SOH\ACK\DC2\EOT\223\EOT\DC1\FS\n\
\\r\n\
\\ENQ\EOT)\STX\SOH\SOH\DC2\EOT\223\EOT\GS'\n\
\\r\n\
\\ENQ\EOT)\STX\SOH\ETX\DC2\EOT\223\EOT23\n\
\\f\n\
\\EOT\EOT)\STX\STX\DC2\EOT\224\EOT\b4\n\
\\r\n\
\\ENQ\EOT)\STX\STX\EOT\DC2\EOT\224\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\STX\ENQ\DC2\EOT\224\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\STX\SOH\DC2\EOT\224\EOT\CAN%\n\
\\r\n\
\\ENQ\EOT)\STX\STX\ETX\DC2\EOT\224\EOT23\n\
\H\n\
\\EOT\EOT)\STX\ETX\DC2\EOT\227\EOT\b8\SUB:/ Total rate of messages delivered to the consumer. msg/s\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\ETX\EOT\DC2\EOT\227\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\ETX\ENQ\DC2\EOT\227\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\ETX\SOH\DC2\EOT\227\EOT\CAN\"\n\
\\r\n\
\\ENQ\EOT)\STX\ETX\ETX\DC2\EOT\227\EOT67\n\
\D\n\
\\EOT\EOT)\STX\EOT\DC2\EOT\230\EOT\b8\SUB6/ Total throughput delivered to the consumer. bytes/s\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\EOT\EOT\DC2\EOT\230\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\EOT\ENQ\DC2\EOT\230\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\EOT\SOH\DC2\EOT\230\EOT\CAN(\n\
\\r\n\
\\ENQ\EOT)\STX\EOT\ETX\DC2\EOT\230\EOT67\n\
\K\n\
\\EOT\EOT)\STX\ENQ\DC2\EOT\233\EOT\b8\SUB=/ Total rate of messages redelivered by this consumer. msg/s\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\ENQ\EOT\DC2\EOT\233\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\ENQ\ENQ\DC2\EOT\233\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\ENQ\SOH\DC2\EOT\233\EOT\CAN(\n\
\\r\n\
\\ENQ\EOT)\STX\ENQ\ETX\DC2\EOT\233\EOT67\n\
\%\n\
\\EOT\EOT)\STX\ACK\DC2\EOT\236\EOT\b8\SUB\ETB/ Name of the consumer\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\ACK\EOT\DC2\EOT\236\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\ACK\ENQ\DC2\EOT\236\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\ACK\SOH\DC2\EOT\236\EOT\CAN$\n\
\\r\n\
\\ENQ\EOT)\STX\ACK\ETX\DC2\EOT\236\EOT67\n\
\E\n\
\\EOT\EOT)\STX\a\DC2\EOT\239\EOT\b8\SUB7/ Number of available message permits for the consumer\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\a\EOT\DC2\EOT\239\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\a\ENQ\DC2\EOT\239\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\a\SOH\DC2\EOT\239\EOT\CAN(\n\
\\r\n\
\\ENQ\EOT)\STX\a\ETX\DC2\EOT\239\EOT67\n\
\C\n\
\\EOT\EOT)\STX\b\DC2\EOT\242\EOT\b8\SUB5/ Number of unacknowledged messages for the consumer\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\b\EOT\DC2\EOT\242\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\b\ENQ\DC2\EOT\242\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\b\SOH\DC2\EOT\242\EOT\CAN'\n\
\\r\n\
\\ENQ\EOT)\STX\b\ETX\DC2\EOT\242\EOT67\n\
\d\n\
\\EOT\EOT)\STX\t\DC2\EOT\245\EOT\b9\SUBV/ Flag to verify if consumer is blocked due to reaching threshold of unacked messages\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\t\EOT\DC2\EOT\245\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\t\ENQ\DC2\EOT\245\EOT\DC1\NAK\n\
\\r\n\
\\ENQ\EOT)\STX\t\SOH\DC2\EOT\245\EOT\SYN2\n\
\\r\n\
\\ENQ\EOT)\STX\t\ETX\DC2\EOT\245\EOT68\n\
\)\n\
\\EOT\EOT)\STX\n\
\\DC2\EOT\248\EOT\b9\SUB\ESC/ Address of this consumer\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\n\
\\EOT\DC2\EOT\248\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\n\
\\ENQ\DC2\EOT\248\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\n\
\\SOH\DC2\EOT\248\EOT\CAN\US\n\
\\r\n\
\\ENQ\EOT)\STX\n\
\\ETX\DC2\EOT\248\EOT68\n\
\(\n\
\\EOT\EOT)\STX\v\DC2\EOT\251\EOT\b9\SUB\SUB/ Timestamp of connection\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\v\EOT\DC2\EOT\251\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\v\ENQ\DC2\EOT\251\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\v\SOH\DC2\EOT\251\EOT\CAN&\n\
\\r\n\
\\ENQ\EOT)\STX\v\ETX\DC2\EOT\251\EOT68\n\
\M\n\
\\EOT\EOT)\STX\f\DC2\EOT\254\EOT\b9\SUB?/ Whether this subscription is Exclusive or Shared or Failover\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\f\EOT\DC2\EOT\254\EOT\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\f\ENQ\DC2\EOT\254\EOT\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\f\SOH\DC2\EOT\254\EOT\CAN\FS\n\
\\r\n\
\\ENQ\EOT)\STX\f\ETX\DC2\EOT\254\EOT68\n\
\K\n\
\\EOT\EOT)\STX\r\DC2\EOT\129\ENQ\b9\SUB=/ Total rate of messages expired on this subscription. msg/s\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\r\EOT\DC2\EOT\129\ENQ\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\r\ENQ\DC2\EOT\129\ENQ\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\r\SOH\DC2\EOT\129\ENQ\CAN&\n\
\\r\n\
\\ENQ\EOT)\STX\r\ETX\DC2\EOT\129\ENQ68\n\
\?\n\
\\EOT\EOT)\STX\SO\DC2\EOT\132\ENQ\b9\SUB1/ Number of messages in the subscription backlog\n\
\\n\
\\r\n\
\\ENQ\EOT)\STX\SO\EOT\DC2\EOT\132\ENQ\b\DLE\n\
\\r\n\
\\ENQ\EOT)\STX\SO\ENQ\DC2\EOT\132\ENQ\DC1\ETB\n\
\\r\n\
\\ENQ\EOT)\STX\SO\SOH\DC2\EOT\132\ENQ\CAN\"\n\
\\r\n\
\\ENQ\EOT)\STX\SO\ETX\DC2\EOT\132\ENQ68\n\
\\f\n\
\\STX\EOT*\DC2\ACK\135\ENQ\NUL\138\ENQ\SOH\n\
\\v\n\
\\ETX\EOT*\SOH\DC2\EOT\135\ENQ\b\US\n\
\\f\n\
\\EOT\EOT*\STX\NUL\DC2\EOT\136\ENQ\EOT$\n\
\\r\n\
\\ENQ\EOT*\STX\NUL\EOT\DC2\EOT\136\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT*\STX\NUL\ENQ\DC2\EOT\136\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT*\STX\NUL\SOH\DC2\EOT\136\ENQ\DC4\US\n\
\\r\n\
\\ENQ\EOT*\STX\NUL\ETX\DC2\EOT\136\ENQ\"#\n\
\\f\n\
\\EOT\EOT*\STX\SOH\DC2\EOT\137\ENQ\EOT$\n\
\\r\n\
\\ENQ\EOT*\STX\SOH\EOT\DC2\EOT\137\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT*\STX\SOH\ENQ\DC2\EOT\137\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT*\STX\SOH\SOH\DC2\EOT\137\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT*\STX\SOH\ETX\DC2\EOT\137\ENQ\"#\n\
\\f\n\
\\STX\EOT+\DC2\ACK\140\ENQ\NUL\143\ENQ\SOH\n\
\\v\n\
\\ETX\EOT+\SOH\DC2\EOT\140\ENQ\b'\n\
\\f\n\
\\EOT\EOT+\STX\NUL\DC2\EOT\141\ENQ\EOT/\n\
\\r\n\
\\ENQ\EOT+\STX\NUL\EOT\DC2\EOT\141\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT+\STX\NUL\ACK\DC2\EOT\141\ENQ\r\SUB\n\
\\r\n\
\\ENQ\EOT+\STX\NUL\SOH\DC2\EOT\141\ENQ\ESC*\n\
\\r\n\
\\ENQ\EOT+\STX\NUL\ETX\DC2\EOT\141\ENQ-.\n\
\\f\n\
\\EOT\EOT+\STX\SOH\DC2\EOT\142\ENQ\EOT$\n\
\\r\n\
\\ENQ\EOT+\STX\SOH\EOT\DC2\EOT\142\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT+\STX\SOH\ENQ\DC2\EOT\142\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT+\STX\SOH\SOH\DC2\EOT\142\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT+\STX\SOH\ETX\DC2\EOT\142\ENQ\"#\n\
\\f\n\
\\STX\EOT,\DC2\ACK\145\ENQ\NUL\154\ENQ\SOH\n\
\\v\n\
\\ETX\EOT,\SOH\DC2\EOT\145\ENQ\b#\n\
\\SO\n\
\\EOT\EOT,\EOT\NUL\DC2\ACK\146\ENQ\EOT\150\ENQ\ENQ\n\
\\r\n\
\\ENQ\EOT,\EOT\NUL\SOH\DC2\EOT\146\ENQ\t\r\n\
\\SO\n\
\\ACK\EOT,\EOT\NUL\STX\NUL\DC2\EOT\147\ENQ\b\ETB\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\NUL\SOH\DC2\EOT\147\ENQ\b\DC2\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\NUL\STX\DC2\EOT\147\ENQ\NAK\SYN\n\
\\SO\n\
\\ACK\EOT,\EOT\NUL\STX\SOH\DC2\EOT\148\ENQ\b\ESC\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\SOH\SOH\DC2\EOT\148\ENQ\b\SYN\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\SOH\STX\DC2\EOT\148\ENQ\EM\SUB\n\
\\SO\n\
\\ACK\EOT,\EOT\NUL\STX\STX\DC2\EOT\149\ENQ\b\DLE\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\STX\SOH\DC2\EOT\149\ENQ\b\v\n\
\\SI\n\
\\a\EOT,\EOT\NUL\STX\STX\STX\DC2\EOT\149\ENQ\SO\SI\n\
\\f\n\
\\EOT\EOT,\STX\NUL\DC2\EOT\151\ENQ\EOT&\n\
\\r\n\
\\ENQ\EOT,\STX\NUL\EOT\DC2\EOT\151\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT,\STX\NUL\ENQ\DC2\EOT\151\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT,\STX\NUL\SOH\DC2\EOT\151\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT,\STX\NUL\ETX\DC2\EOT\151\ENQ$%\n\
\\f\n\
\\EOT\EOT,\STX\SOH\DC2\EOT\152\ENQ\EOT%\n\
\\r\n\
\\ENQ\EOT,\STX\SOH\EOT\DC2\EOT\152\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT,\STX\SOH\ENQ\DC2\EOT\152\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT,\STX\SOH\SOH\DC2\EOT\152\ENQ\DC4\GS\n\
\\r\n\
\\ENQ\EOT,\STX\SOH\ETX\DC2\EOT\152\ENQ#$\n\
\\f\n\
\\EOT\EOT,\STX\STX\DC2\EOT\153\ENQ\EOT2\n\
\\r\n\
\\ENQ\EOT,\STX\STX\EOT\DC2\EOT\153\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT,\STX\STX\ACK\DC2\EOT\153\ENQ\r\DC1\n\
\\r\n\
\\ENQ\EOT,\STX\STX\SOH\DC2\EOT\153\ENQ\DC2\SYN\n\
\\r\n\
\\ENQ\EOT,\STX\STX\ETX\DC2\EOT\153\ENQ\EM\SUB\n\
\\r\n\
\\ENQ\EOT,\STX\STX\b\DC2\EOT\153\ENQ\ESC1\n\
\\r\n\
\\ENQ\EOT,\STX\STX\a\DC2\EOT\153\ENQ&0\n\
\\f\n\
\\STX\EOT-\DC2\ACK\156\ENQ\NUL\159\ENQ\SOH\n\
\\v\n\
\\ETX\EOT-\SOH\DC2\EOT\156\ENQ\b+\n\
\\f\n\
\\EOT\EOT-\STX\NUL\DC2\EOT\157\ENQ\EOT&\n\
\\r\n\
\\ENQ\EOT-\STX\NUL\EOT\DC2\EOT\157\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT-\STX\NUL\ENQ\DC2\EOT\157\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT-\STX\NUL\SOH\DC2\EOT\157\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT-\STX\NUL\ETX\DC2\EOT\157\ENQ$%\n\
\\f\n\
\\EOT\EOT-\STX\SOH\DC2\EOT\158\ENQ\EOT'\n\
\\r\n\
\\ENQ\EOT-\STX\SOH\EOT\DC2\EOT\158\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT-\STX\SOH\ENQ\DC2\EOT\158\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT-\STX\SOH\SOH\DC2\EOT\158\ENQ\DC4\SUB\n\
\\r\n\
\\ENQ\EOT-\STX\SOH\ETX\DC2\EOT\158\ENQ%&\n\
\\f\n\
\\STX\EOT.\DC2\ACK\161\ENQ\NUL\166\ENQ\SOH\n\
\\v\n\
\\ETX\EOT.\SOH\DC2\EOT\161\ENQ\b\CAN\n\
\\f\n\
\\EOT\EOT.\STX\NUL\DC2\EOT\162\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT.\STX\NUL\EOT\DC2\EOT\162\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT.\STX\NUL\ENQ\DC2\EOT\162\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT.\STX\NUL\SOH\DC2\EOT\162\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT.\STX\NUL\ETX\DC2\EOT\162\ENQ!\"\n\
\\f\n\
\\EOT\EOT.\STX\SOH\DC2\EOT\163\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT.\STX\SOH\EOT\DC2\EOT\163\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT.\STX\SOH\ENQ\DC2\EOT\163\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT.\STX\SOH\SOH\DC2\EOT\163\ENQ\DC4\EM\n\
\\r\n\
\\ENQ\EOT.\STX\SOH\ETX\DC2\EOT\163\ENQ!\"\n\
\\f\n\
\\EOT\EOT.\STX\STX\DC2\EOT\165\ENQ\EOT&\n\
\\r\n\
\\ENQ\EOT.\STX\STX\EOT\DC2\EOT\165\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT.\STX\STX\ENQ\DC2\EOT\165\ENQ\r\DC2\n\
\\r\n\
\\ENQ\EOT.\STX\STX\SOH\DC2\EOT\165\ENQ\DC3!\n\
\\r\n\
\\ENQ\EOT.\STX\STX\ETX\DC2\EOT\165\ENQ$%\n\
\\f\n\
\\STX\EOT/\DC2\ACK\168\ENQ\NUL\175\ENQ\SOH\n\
\\v\n\
\\ETX\EOT/\SOH\DC2\EOT\168\ENQ\b \n\
\\f\n\
\\EOT\EOT/\STX\NUL\DC2\EOT\169\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT/\STX\NUL\EOT\DC2\EOT\169\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT/\STX\NUL\ENQ\DC2\EOT\169\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT/\STX\NUL\SOH\DC2\EOT\169\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT/\STX\NUL\ETX\DC2\EOT\169\ENQ&'\n\
\\f\n\
\\EOT\EOT/\STX\SOH\DC2\EOT\170\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT/\STX\SOH\EOT\DC2\EOT\170\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT/\STX\SOH\ACK\DC2\EOT\170\ENQ\r\CAN\n\
\\r\n\
\\ENQ\EOT/\STX\SOH\SOH\DC2\EOT\170\ENQ\EM#\n\
\\r\n\
\\ENQ\EOT/\STX\SOH\ETX\DC2\EOT\170\ENQ&'\n\
\\f\n\
\\EOT\EOT/\STX\STX\DC2\EOT\171\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT/\STX\STX\EOT\DC2\EOT\171\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT/\STX\STX\ENQ\DC2\EOT\171\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT/\STX\STX\SOH\DC2\EOT\171\ENQ\DC4!\n\
\\r\n\
\\ENQ\EOT/\STX\STX\ETX\DC2\EOT\171\ENQ&'\n\
\\f\n\
\\EOT\EOT/\STX\ETX\DC2\EOT\173\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT/\STX\ETX\EOT\DC2\EOT\173\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT/\STX\ETX\ACK\DC2\EOT\173\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT/\STX\ETX\SOH\DC2\EOT\173\ENQ\DC4\SUB\n\
\\r\n\
\\ENQ\EOT/\STX\ETX\ETX\DC2\EOT\173\ENQ&'\n\
\\f\n\
\\EOT\EOT/\STX\EOT\DC2\EOT\174\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT/\STX\EOT\EOT\DC2\EOT\174\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT/\STX\EOT\ENQ\DC2\EOT\174\ENQ\r\DC2\n\
\\r\n\
\\ENQ\EOT/\STX\EOT\SOH\DC2\EOT\174\ENQ\DC3!\n\
\\r\n\
\\ENQ\EOT/\STX\EOT\ETX\DC2\EOT\174\ENQ&'\n\
\\f\n\
\\STX\EOT0\DC2\ACK\177\ENQ\NUL\181\ENQ\SOH\n\
\\v\n\
\\ETX\EOT0\SOH\DC2\EOT\177\ENQ\b \n\
\\f\n\
\\EOT\EOT0\STX\NUL\DC2\EOT\178\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT0\STX\NUL\EOT\DC2\EOT\178\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT0\STX\NUL\ENQ\DC2\EOT\178\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT0\STX\NUL\SOH\DC2\EOT\178\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT0\STX\NUL\ETX\DC2\EOT\178\ENQ!\"\n\
\\f\n\
\\EOT\EOT0\STX\SOH\DC2\EOT\179\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT0\STX\SOH\EOT\DC2\EOT\179\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT0\STX\SOH\ENQ\DC2\EOT\179\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT0\STX\SOH\SOH\DC2\EOT\179\ENQ\DC4\EM\n\
\\r\n\
\\ENQ\EOT0\STX\SOH\ETX\DC2\EOT\179\ENQ!\"\n\
\\f\n\
\\EOT\EOT0\STX\STX\DC2\EOT\180\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT0\STX\STX\EOT\DC2\EOT\180\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT0\STX\STX\ACK\DC2\EOT\180\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT0\STX\STX\SOH\DC2\EOT\180\ENQ\DC4\SUB\n\
\\r\n\
\\ENQ\EOT0\STX\STX\ETX\DC2\EOT\180\ENQ!\"\n\
\\f\n\
\\STX\EOT1\DC2\ACK\183\ENQ\NUL\189\ENQ\SOH\n\
\\v\n\
\\ETX\EOT1\SOH\DC2\EOT\183\ENQ\b(\n\
\\f\n\
\\EOT\EOT1\STX\NUL\DC2\EOT\184\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT1\STX\NUL\EOT\DC2\EOT\184\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT1\STX\NUL\ENQ\DC2\EOT\184\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT1\STX\NUL\SOH\DC2\EOT\184\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT1\STX\NUL\ETX\DC2\EOT\184\ENQ&'\n\
\\f\n\
\\EOT\EOT1\STX\SOH\DC2\EOT\185\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT1\STX\SOH\EOT\DC2\EOT\185\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT1\STX\SOH\ACK\DC2\EOT\185\ENQ\r\CAN\n\
\\r\n\
\\ENQ\EOT1\STX\SOH\SOH\DC2\EOT\185\ENQ\EM#\n\
\\r\n\
\\ENQ\EOT1\STX\SOH\ETX\DC2\EOT\185\ENQ&'\n\
\\f\n\
\\EOT\EOT1\STX\STX\DC2\EOT\186\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT1\STX\STX\EOT\DC2\EOT\186\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT1\STX\STX\ENQ\DC2\EOT\186\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT1\STX\STX\SOH\DC2\EOT\186\ENQ\DC4!\n\
\\r\n\
\\ENQ\EOT1\STX\STX\ETX\DC2\EOT\186\ENQ&'\n\
\\f\n\
\\EOT\EOT1\STX\ETX\DC2\EOT\188\ENQ\EOT(\n\
\\r\n\
\\ENQ\EOT1\STX\ETX\EOT\DC2\EOT\188\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT1\STX\ETX\ENQ\DC2\EOT\188\ENQ\r\DC2\n\
\\r\n\
\\ENQ\EOT1\STX\ETX\SOH\DC2\EOT\188\ENQ\DC3!\n\
\\r\n\
\\ENQ\EOT1\STX\ETX\ETX\DC2\EOT\188\ENQ&'\n\
\,\n\
\\STX\ENQ\ENQ\DC2\ACK\193\ENQ\NUL\196\ENQ\SOH2\RS/ --- transaction related ---\n\
\\n\
\\v\n\
\\ETX\ENQ\ENQ\SOH\DC2\EOT\193\ENQ\ENQ\SO\n\
\\f\n\
\\EOT\ENQ\ENQ\STX\NUL\DC2\EOT\194\ENQ\EOT\SI\n\
\\r\n\
\\ENQ\ENQ\ENQ\STX\NUL\SOH\DC2\EOT\194\ENQ\EOT\n\
\\n\
\\r\n\
\\ENQ\ENQ\ENQ\STX\NUL\STX\DC2\EOT\194\ENQ\r\SO\n\
\\f\n\
\\EOT\ENQ\ENQ\STX\SOH\DC2\EOT\195\ENQ\EOT\SO\n\
\\r\n\
\\ENQ\ENQ\ENQ\STX\SOH\SOH\DC2\EOT\195\ENQ\EOT\t\n\
\\r\n\
\\ENQ\ENQ\ENQ\STX\SOH\STX\DC2\EOT\195\ENQ\f\r\n\
\\f\n\
\\STX\EOT2\DC2\ACK\198\ENQ\NUL\202\ENQ\SOH\n\
\\v\n\
\\ETX\EOT2\SOH\DC2\EOT\198\ENQ\b\NAK\n\
\\f\n\
\\EOT\EOT2\STX\NUL\DC2\EOT\199\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT2\STX\NUL\EOT\DC2\EOT\199\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT2\STX\NUL\ENQ\DC2\EOT\199\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT2\STX\NUL\SOH\DC2\EOT\199\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT2\STX\NUL\ETX\DC2\EOT\199\ENQ!\"\n\
\\f\n\
\\EOT\EOT2\STX\SOH\DC2\EOT\200\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\EOT\DC2\EOT\200\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\ENQ\DC2\EOT\200\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\SOH\DC2\EOT\200\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\ETX\DC2\EOT\200\ENQ&'\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\b\DC2\EOT\200\ENQ(5\n\
\\r\n\
\\ENQ\EOT2\STX\SOH\a\DC2\EOT\200\ENQ34\n\
\\f\n\
\\EOT\EOT2\STX\STX\DC2\EOT\201\ENQ\EOT,\n\
\\r\n\
\\ENQ\EOT2\STX\STX\EOT\DC2\EOT\201\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT2\STX\STX\ENQ\DC2\EOT\201\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT2\STX\STX\SOH\DC2\EOT\201\ENQ\DC4\EM\n\
\\r\n\
\\ENQ\EOT2\STX\STX\ETX\DC2\EOT\201\ENQ\FS\GS\n\
\\r\n\
\\ENQ\EOT2\STX\STX\b\DC2\EOT\201\ENQ\RS+\n\
\\r\n\
\\ENQ\EOT2\STX\STX\a\DC2\EOT\201\ENQ)*\n\
\\f\n\
\\STX\EOT3\DC2\ACK\204\ENQ\NUL\210\ENQ\SOH\n\
\\v\n\
\\ETX\EOT3\SOH\DC2\EOT\204\ENQ\b\GS\n\
\\f\n\
\\EOT\EOT3\STX\NUL\DC2\EOT\205\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT3\STX\NUL\EOT\DC2\EOT\205\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT3\STX\NUL\ENQ\DC2\EOT\205\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT3\STX\NUL\SOH\DC2\EOT\205\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT3\STX\NUL\ETX\DC2\EOT\205\ENQ!\"\n\
\\f\n\
\\EOT\EOT3\STX\SOH\DC2\EOT\206\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\EOT\DC2\EOT\206\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\ENQ\DC2\EOT\206\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\SOH\DC2\EOT\206\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\ETX\DC2\EOT\206\ENQ'(\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\b\DC2\EOT\206\ENQ)6\n\
\\r\n\
\\ENQ\EOT3\STX\SOH\a\DC2\EOT\206\ENQ45\n\
\\f\n\
\\EOT\EOT3\STX\STX\DC2\EOT\207\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT3\STX\STX\EOT\DC2\EOT\207\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT3\STX\STX\ENQ\DC2\EOT\207\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT3\STX\STX\SOH\DC2\EOT\207\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT3\STX\STX\ETX\DC2\EOT\207\ENQ&'\n\
\\r\n\
\\ENQ\EOT3\STX\STX\b\DC2\EOT\207\ENQ(5\n\
\\r\n\
\\ENQ\EOT3\STX\STX\a\DC2\EOT\207\ENQ34\n\
\\f\n\
\\EOT\EOT3\STX\ETX\DC2\EOT\208\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT3\STX\ETX\EOT\DC2\EOT\208\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT3\STX\ETX\ACK\DC2\EOT\208\ENQ\r\CAN\n\
\\r\n\
\\ENQ\EOT3\STX\ETX\SOH\DC2\EOT\208\ENQ\EM\RS\n\
\\r\n\
\\ENQ\EOT3\STX\ETX\ETX\DC2\EOT\208\ENQ!\"\n\
\\f\n\
\\EOT\EOT3\STX\EOT\DC2\EOT\209\ENQ\EOT \n\
\\r\n\
\\ENQ\EOT3\STX\EOT\EOT\DC2\EOT\209\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT3\STX\EOT\ENQ\DC2\EOT\209\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT3\STX\EOT\SOH\DC2\EOT\209\ENQ\DC4\ESC\n\
\\r\n\
\\ENQ\EOT3\STX\EOT\ETX\DC2\EOT\209\ENQ\RS\US\n\
\\f\n\
\\STX\EOT4\DC2\ACK\212\ENQ\NUL\217\ENQ\SOH\n\
\\v\n\
\\ETX\EOT4\SOH\DC2\EOT\212\ENQ\b \n\
\\f\n\
\\EOT\EOT4\STX\NUL\DC2\EOT\213\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT4\STX\NUL\EOT\DC2\EOT\213\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT4\STX\NUL\ENQ\DC2\EOT\213\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT4\STX\NUL\SOH\DC2\EOT\213\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT4\STX\NUL\ETX\DC2\EOT\213\ENQ!\"\n\
\\f\n\
\\EOT\EOT4\STX\SOH\DC2\EOT\214\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\EOT\DC2\EOT\214\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\ENQ\DC2\EOT\214\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\SOH\DC2\EOT\214\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\ETX\DC2\EOT\214\ENQ'(\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\b\DC2\EOT\214\ENQ)6\n\
\\r\n\
\\ENQ\EOT4\STX\SOH\a\DC2\EOT\214\ENQ45\n\
\\f\n\
\\EOT\EOT4\STX\STX\DC2\EOT\215\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT4\STX\STX\EOT\DC2\EOT\215\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT4\STX\STX\ENQ\DC2\EOT\215\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT4\STX\STX\SOH\DC2\EOT\215\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT4\STX\STX\ETX\DC2\EOT\215\ENQ&'\n\
\\r\n\
\\ENQ\EOT4\STX\STX\b\DC2\EOT\215\ENQ(5\n\
\\r\n\
\\ENQ\EOT4\STX\STX\a\DC2\EOT\215\ENQ34\n\
\\f\n\
\\EOT\EOT4\STX\ETX\DC2\EOT\216\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT4\STX\ETX\EOT\DC2\EOT\216\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT4\STX\ETX\ENQ\DC2\EOT\216\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT4\STX\ETX\SOH\DC2\EOT\216\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT4\STX\ETX\ETX\DC2\EOT\216\ENQ!\"\n\
\\f\n\
\\STX\EOT5\DC2\ACK\219\ENQ\NUL\225\ENQ\SOH\n\
\\v\n\
\\ETX\EOT5\SOH\DC2\EOT\219\ENQ\b(\n\
\\f\n\
\\EOT\EOT5\STX\NUL\DC2\EOT\220\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT5\STX\NUL\EOT\DC2\EOT\220\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT5\STX\NUL\ENQ\DC2\EOT\220\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT5\STX\NUL\SOH\DC2\EOT\220\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT5\STX\NUL\ETX\DC2\EOT\220\ENQ!\"\n\
\\f\n\
\\EOT\EOT5\STX\SOH\DC2\EOT\221\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\EOT\DC2\EOT\221\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\ENQ\DC2\EOT\221\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\SOH\DC2\EOT\221\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\ETX\DC2\EOT\221\ENQ'(\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\b\DC2\EOT\221\ENQ)6\n\
\\r\n\
\\ENQ\EOT5\STX\SOH\a\DC2\EOT\221\ENQ45\n\
\\f\n\
\\EOT\EOT5\STX\STX\DC2\EOT\222\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT5\STX\STX\EOT\DC2\EOT\222\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT5\STX\STX\ENQ\DC2\EOT\222\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT5\STX\STX\SOH\DC2\EOT\222\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT5\STX\STX\ETX\DC2\EOT\222\ENQ&'\n\
\\r\n\
\\ENQ\EOT5\STX\STX\b\DC2\EOT\222\ENQ(5\n\
\\r\n\
\\ENQ\EOT5\STX\STX\a\DC2\EOT\222\ENQ34\n\
\\f\n\
\\EOT\EOT5\STX\ETX\DC2\EOT\223\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT5\STX\ETX\EOT\DC2\EOT\223\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT5\STX\ETX\ACK\DC2\EOT\223\ENQ\r\CAN\n\
\\r\n\
\\ENQ\EOT5\STX\ETX\SOH\DC2\EOT\223\ENQ\EM\RS\n\
\\r\n\
\\ENQ\EOT5\STX\ETX\ETX\DC2\EOT\223\ENQ!\"\n\
\\f\n\
\\EOT\EOT5\STX\EOT\DC2\EOT\224\ENQ\EOT \n\
\\r\n\
\\ENQ\EOT5\STX\EOT\EOT\DC2\EOT\224\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT5\STX\EOT\ENQ\DC2\EOT\224\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT5\STX\EOT\SOH\DC2\EOT\224\ENQ\DC4\ESC\n\
\\r\n\
\\ENQ\EOT5\STX\EOT\ETX\DC2\EOT\224\ENQ\RS\US\n\
\\f\n\
\\STX\EOT6\DC2\ACK\227\ENQ\NUL\230\ENQ\SOH\n\
\\v\n\
\\ETX\EOT6\SOH\DC2\EOT\227\ENQ\b\DC4\n\
\\f\n\
\\EOT\EOT6\STX\NUL\DC2\EOT\228\ENQ\EOT\RS\n\
\\r\n\
\\ENQ\EOT6\STX\NUL\EOT\DC2\EOT\228\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT6\STX\NUL\ENQ\DC2\EOT\228\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT6\STX\NUL\SOH\DC2\EOT\228\ENQ\DC4\EM\n\
\\r\n\
\\ENQ\EOT6\STX\NUL\ETX\DC2\EOT\228\ENQ\FS\GS\n\
\\f\n\
\\EOT\EOT6\STX\SOH\DC2\EOT\229\ENQ\EOT%\n\
\\r\n\
\\ENQ\EOT6\STX\SOH\EOT\DC2\EOT\229\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT6\STX\SOH\ENQ\DC2\EOT\229\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT6\STX\SOH\SOH\DC2\EOT\229\ENQ\DC4 \n\
\\r\n\
\\ENQ\EOT6\STX\SOH\ETX\DC2\EOT\229\ENQ#$\n\
\\f\n\
\\STX\EOT7\DC2\ACK\231\ENQ\NUL\236\ENQ\SOH\n\
\\v\n\
\\ETX\EOT7\SOH\DC2\EOT\231\ENQ\b#\n\
\\f\n\
\\EOT\EOT7\STX\NUL\DC2\EOT\232\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT7\STX\NUL\EOT\DC2\EOT\232\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT7\STX\NUL\ENQ\DC2\EOT\232\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT7\STX\NUL\SOH\DC2\EOT\232\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT7\STX\NUL\ETX\DC2\EOT\232\ENQ!\"\n\
\\f\n\
\\EOT\EOT7\STX\SOH\DC2\EOT\233\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\EOT\DC2\EOT\233\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\ENQ\DC2\EOT\233\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\SOH\DC2\EOT\233\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\ETX\DC2\EOT\233\ENQ'(\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\b\DC2\EOT\233\ENQ)6\n\
\\r\n\
\\ENQ\EOT7\STX\SOH\a\DC2\EOT\233\ENQ45\n\
\\f\n\
\\EOT\EOT7\STX\STX\DC2\EOT\234\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT7\STX\STX\EOT\DC2\EOT\234\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT7\STX\STX\ENQ\DC2\EOT\234\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT7\STX\STX\SOH\DC2\EOT\234\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT7\STX\STX\ETX\DC2\EOT\234\ENQ&'\n\
\\r\n\
\\ENQ\EOT7\STX\STX\b\DC2\EOT\234\ENQ(5\n\
\\r\n\
\\ENQ\EOT7\STX\STX\a\DC2\EOT\234\ENQ34\n\
\\f\n\
\\EOT\EOT7\STX\ETX\DC2\EOT\235\ENQ\EOT+\n\
\\r\n\
\\ENQ\EOT7\STX\ETX\EOT\DC2\EOT\235\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT7\STX\ETX\ACK\DC2\EOT\235\ENQ\r\EM\n\
\\r\n\
\\ENQ\EOT7\STX\ETX\SOH\DC2\EOT\235\ENQ\SUB&\n\
\\r\n\
\\ENQ\EOT7\STX\ETX\ETX\DC2\EOT\235\ENQ)*\n\
\\f\n\
\\STX\EOT8\DC2\ACK\238\ENQ\NUL\244\ENQ\SOH\n\
\\v\n\
\\ETX\EOT8\SOH\DC2\EOT\238\ENQ\b+\n\
\\f\n\
\\EOT\EOT8\STX\NUL\DC2\EOT\239\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT8\STX\NUL\EOT\DC2\EOT\239\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT8\STX\NUL\ENQ\DC2\EOT\239\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT8\STX\NUL\SOH\DC2\EOT\239\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT8\STX\NUL\ETX\DC2\EOT\239\ENQ!\"\n\
\\f\n\
\\EOT\EOT8\STX\SOH\DC2\EOT\240\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\EOT\DC2\EOT\240\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\ENQ\DC2\EOT\240\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\SOH\DC2\EOT\240\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\ETX\DC2\EOT\240\ENQ'(\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\b\DC2\EOT\240\ENQ)6\n\
\\r\n\
\\ENQ\EOT8\STX\SOH\a\DC2\EOT\240\ENQ45\n\
\\f\n\
\\EOT\EOT8\STX\STX\DC2\EOT\241\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT8\STX\STX\EOT\DC2\EOT\241\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT8\STX\STX\ENQ\DC2\EOT\241\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT8\STX\STX\SOH\DC2\EOT\241\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT8\STX\STX\ETX\DC2\EOT\241\ENQ&'\n\
\\r\n\
\\ENQ\EOT8\STX\STX\b\DC2\EOT\241\ENQ(5\n\
\\r\n\
\\ENQ\EOT8\STX\STX\a\DC2\EOT\241\ENQ34\n\
\\f\n\
\\EOT\EOT8\STX\ETX\DC2\EOT\242\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT8\STX\ETX\EOT\DC2\EOT\242\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT8\STX\ETX\ACK\DC2\EOT\242\ENQ\r\CAN\n\
\\r\n\
\\ENQ\EOT8\STX\ETX\SOH\DC2\EOT\242\ENQ\EM\RS\n\
\\r\n\
\\ENQ\EOT8\STX\ETX\ETX\DC2\EOT\242\ENQ!\"\n\
\\f\n\
\\EOT\EOT8\STX\EOT\DC2\EOT\243\ENQ\EOT \n\
\\r\n\
\\ENQ\EOT8\STX\EOT\EOT\DC2\EOT\243\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT8\STX\EOT\ENQ\DC2\EOT\243\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT8\STX\EOT\SOH\DC2\EOT\243\ENQ\DC4\ESC\n\
\\r\n\
\\ENQ\EOT8\STX\EOT\ETX\DC2\EOT\243\ENQ\RS\US\n\
\\f\n\
\\STX\EOT9\DC2\ACK\246\ENQ\NUL\251\ENQ\SOH\n\
\\v\n\
\\ETX\EOT9\SOH\DC2\EOT\246\ENQ\b\NAK\n\
\\f\n\
\\EOT\EOT9\STX\NUL\DC2\EOT\247\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT9\STX\NUL\EOT\DC2\EOT\247\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT9\STX\NUL\ENQ\DC2\EOT\247\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT9\STX\NUL\SOH\DC2\EOT\247\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT9\STX\NUL\ETX\DC2\EOT\247\ENQ!\"\n\
\\f\n\
\\EOT\EOT9\STX\SOH\DC2\EOT\248\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\EOT\DC2\EOT\248\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\ENQ\DC2\EOT\248\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\SOH\DC2\EOT\248\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\ETX\DC2\EOT\248\ENQ'(\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\b\DC2\EOT\248\ENQ)6\n\
\\r\n\
\\ENQ\EOT9\STX\SOH\a\DC2\EOT\248\ENQ45\n\
\\f\n\
\\EOT\EOT9\STX\STX\DC2\EOT\249\ENQ\EOT6\n\
\\r\n\
\\ENQ\EOT9\STX\STX\EOT\DC2\EOT\249\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT9\STX\STX\ENQ\DC2\EOT\249\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT9\STX\STX\SOH\DC2\EOT\249\ENQ\DC4#\n\
\\r\n\
\\ENQ\EOT9\STX\STX\ETX\DC2\EOT\249\ENQ&'\n\
\\r\n\
\\ENQ\EOT9\STX\STX\b\DC2\EOT\249\ENQ(5\n\
\\r\n\
\\ENQ\EOT9\STX\STX\a\DC2\EOT\249\ENQ34\n\
\\f\n\
\\EOT\EOT9\STX\ETX\DC2\EOT\250\ENQ\EOT&\n\
\\r\n\
\\ENQ\EOT9\STX\ETX\EOT\DC2\EOT\250\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT9\STX\ETX\ACK\DC2\EOT\250\ENQ\r\SYN\n\
\\r\n\
\\ENQ\EOT9\STX\ETX\SOH\DC2\EOT\250\ENQ\ETB!\n\
\\r\n\
\\ENQ\EOT9\STX\ETX\ETX\DC2\EOT\250\ENQ$%\n\
\\f\n\
\\STX\EOT:\DC2\ACK\253\ENQ\NUL\131\ACK\SOH\n\
\\v\n\
\\ETX\EOT:\SOH\DC2\EOT\253\ENQ\b\GS\n\
\\f\n\
\\EOT\EOT:\STX\NUL\DC2\EOT\254\ENQ\EOT#\n\
\\r\n\
\\ENQ\EOT:\STX\NUL\EOT\DC2\EOT\254\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT:\STX\NUL\ENQ\DC2\EOT\254\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT:\STX\NUL\SOH\DC2\EOT\254\ENQ\DC4\RS\n\
\\r\n\
\\ENQ\EOT:\STX\NUL\ETX\DC2\EOT\254\ENQ!\"\n\
\\f\n\
\\EOT\EOT:\STX\SOH\DC2\EOT\255\ENQ\EOT7\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\EOT\DC2\EOT\255\ENQ\EOT\f\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\ENQ\DC2\EOT\255\ENQ\r\DC3\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\SOH\DC2\EOT\255\ENQ\DC4$\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\ETX\DC2\EOT\255\ENQ'(\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\b\DC2\EOT\255\ENQ)6\n\
\\r\n\
\\ENQ\EOT:\STX\SOH\a\DC2\EOT\255\ENQ45\n\
\\f\n\
\\EOT\EOT:\STX\STX\DC2\EOT\128\ACK\EOT6\n\
\\r\n\
\\ENQ\EOT:\STX\STX\EOT\DC2\EOT\128\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT:\STX\STX\ENQ\DC2\EOT\128\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT:\STX\STX\SOH\DC2\EOT\128\ACK\DC4#\n\
\\r\n\
\\ENQ\EOT:\STX\STX\ETX\DC2\EOT\128\ACK&'\n\
\\r\n\
\\ENQ\EOT:\STX\STX\b\DC2\EOT\128\ACK(5\n\
\\r\n\
\\ENQ\EOT:\STX\STX\a\DC2\EOT\128\ACK34\n\
\\f\n\
\\EOT\EOT:\STX\ETX\DC2\EOT\129\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT:\STX\ETX\EOT\DC2\EOT\129\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT:\STX\ETX\ACK\DC2\EOT\129\ACK\r\CAN\n\
\\r\n\
\\ENQ\EOT:\STX\ETX\SOH\DC2\EOT\129\ACK\EM\RS\n\
\\r\n\
\\ENQ\EOT:\STX\ETX\ETX\DC2\EOT\129\ACK!\"\n\
\\f\n\
\\EOT\EOT:\STX\EOT\DC2\EOT\130\ACK\EOT \n\
\\r\n\
\\ENQ\EOT:\STX\EOT\EOT\DC2\EOT\130\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT:\STX\EOT\ENQ\DC2\EOT\130\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT:\STX\EOT\SOH\DC2\EOT\130\ACK\DC4\ESC\n\
\\r\n\
\\ENQ\EOT:\STX\EOT\ETX\DC2\EOT\130\ACK\RS\US\n\
\\f\n\
\\STX\EOT;\DC2\ACK\133\ACK\NUL\139\ACK\SOH\n\
\\v\n\
\\ETX\EOT;\SOH\DC2\EOT\133\ACK\b \n\
\\f\n\
\\EOT\EOT;\STX\NUL\DC2\EOT\134\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT;\STX\NUL\EOT\DC2\EOT\134\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT;\STX\NUL\ENQ\DC2\EOT\134\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT;\STX\NUL\SOH\DC2\EOT\134\ACK\DC4\RS\n\
\\r\n\
\\ENQ\EOT;\STX\NUL\ETX\DC2\EOT\134\ACK!\"\n\
\\f\n\
\\EOT\EOT;\STX\SOH\DC2\EOT\135\ACK\EOT7\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\EOT\DC2\EOT\135\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\ENQ\DC2\EOT\135\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\SOH\DC2\EOT\135\ACK\DC4$\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\ETX\DC2\EOT\135\ACK'(\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\b\DC2\EOT\135\ACK)6\n\
\\r\n\
\\ENQ\EOT;\STX\SOH\a\DC2\EOT\135\ACK45\n\
\\f\n\
\\EOT\EOT;\STX\STX\DC2\EOT\136\ACK\EOT6\n\
\\r\n\
\\ENQ\EOT;\STX\STX\EOT\DC2\EOT\136\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT;\STX\STX\ENQ\DC2\EOT\136\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT;\STX\STX\SOH\DC2\EOT\136\ACK\DC4#\n\
\\r\n\
\\ENQ\EOT;\STX\STX\ETX\DC2\EOT\136\ACK&'\n\
\\r\n\
\\ENQ\EOT;\STX\STX\b\DC2\EOT\136\ACK(5\n\
\\r\n\
\\ENQ\EOT;\STX\STX\a\DC2\EOT\136\ACK34\n\
\\f\n\
\\EOT\EOT;\STX\ETX\DC2\EOT\137\ACK\EOT\RS\n\
\\r\n\
\\ENQ\EOT;\STX\ETX\EOT\DC2\EOT\137\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT;\STX\ETX\ENQ\DC2\EOT\137\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT;\STX\ETX\SOH\DC2\EOT\137\ACK\DC4\EM\n\
\\r\n\
\\ENQ\EOT;\STX\ETX\ETX\DC2\EOT\137\ACK\FS\GS\n\
\\f\n\
\\EOT\EOT;\STX\EOT\DC2\EOT\138\ACK\EOT&\n\
\\r\n\
\\ENQ\EOT;\STX\EOT\EOT\DC2\EOT\138\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT;\STX\EOT\ACK\DC2\EOT\138\ACK\r\SYN\n\
\\r\n\
\\ENQ\EOT;\STX\EOT\SOH\DC2\EOT\138\ACK\ETB!\n\
\\r\n\
\\ENQ\EOT;\STX\EOT\ETX\DC2\EOT\138\ACK$%\n\
\\f\n\
\\STX\EOT<\DC2\ACK\141\ACK\NUL\147\ACK\SOH\n\
\\v\n\
\\ETX\EOT<\SOH\DC2\EOT\141\ACK\b(\n\
\\f\n\
\\EOT\EOT<\STX\NUL\DC2\EOT\142\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT<\STX\NUL\EOT\DC2\EOT\142\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT<\STX\NUL\ENQ\DC2\EOT\142\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT<\STX\NUL\SOH\DC2\EOT\142\ACK\DC4\RS\n\
\\r\n\
\\ENQ\EOT<\STX\NUL\ETX\DC2\EOT\142\ACK!\"\n\
\\f\n\
\\EOT\EOT<\STX\SOH\DC2\EOT\143\ACK\EOT7\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\EOT\DC2\EOT\143\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\ENQ\DC2\EOT\143\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\SOH\DC2\EOT\143\ACK\DC4$\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\ETX\DC2\EOT\143\ACK'(\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\b\DC2\EOT\143\ACK)6\n\
\\r\n\
\\ENQ\EOT<\STX\SOH\a\DC2\EOT\143\ACK45\n\
\\f\n\
\\EOT\EOT<\STX\STX\DC2\EOT\144\ACK\EOT6\n\
\\r\n\
\\ENQ\EOT<\STX\STX\EOT\DC2\EOT\144\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT<\STX\STX\ENQ\DC2\EOT\144\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT<\STX\STX\SOH\DC2\EOT\144\ACK\DC4#\n\
\\r\n\
\\ENQ\EOT<\STX\STX\ETX\DC2\EOT\144\ACK&'\n\
\\r\n\
\\ENQ\EOT<\STX\STX\b\DC2\EOT\144\ACK(5\n\
\\r\n\
\\ENQ\EOT<\STX\STX\a\DC2\EOT\144\ACK34\n\
\\f\n\
\\EOT\EOT<\STX\ETX\DC2\EOT\145\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT<\STX\ETX\EOT\DC2\EOT\145\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT<\STX\ETX\ACK\DC2\EOT\145\ACK\r\CAN\n\
\\r\n\
\\ENQ\EOT<\STX\ETX\SOH\DC2\EOT\145\ACK\EM\RS\n\
\\r\n\
\\ENQ\EOT<\STX\ETX\ETX\DC2\EOT\145\ACK!\"\n\
\\f\n\
\\EOT\EOT<\STX\EOT\DC2\EOT\146\ACK\EOT \n\
\\r\n\
\\ENQ\EOT<\STX\EOT\EOT\DC2\EOT\146\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT<\STX\EOT\ENQ\DC2\EOT\146\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT<\STX\EOT\SOH\DC2\EOT\146\ACK\DC4\ESC\n\
\\r\n\
\\ENQ\EOT<\STX\EOT\ETX\DC2\EOT\146\ACK\RS\US\n\
\\f\n\
\\STX\EOT=\DC2\ACK\149\ACK\NUL\155\ACK\SOH\n\
\\v\n\
\\ETX\EOT=\SOH\DC2\EOT\149\ACK\b#\n\
\\f\n\
\\EOT\EOT=\STX\NUL\DC2\EOT\150\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT=\STX\NUL\EOT\DC2\EOT\150\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT=\STX\NUL\ENQ\DC2\EOT\150\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT=\STX\NUL\SOH\DC2\EOT\150\ACK\DC4\RS\n\
\\r\n\
\\ENQ\EOT=\STX\NUL\ETX\DC2\EOT\150\ACK!\"\n\
\\f\n\
\\EOT\EOT=\STX\SOH\DC2\EOT\151\ACK\EOT7\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\EOT\DC2\EOT\151\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\ENQ\DC2\EOT\151\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\SOH\DC2\EOT\151\ACK\DC4$\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\ETX\DC2\EOT\151\ACK'(\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\b\DC2\EOT\151\ACK)6\n\
\\r\n\
\\ENQ\EOT=\STX\SOH\a\DC2\EOT\151\ACK45\n\
\\f\n\
\\EOT\EOT=\STX\STX\DC2\EOT\152\ACK\EOT6\n\
\\r\n\
\\ENQ\EOT=\STX\STX\EOT\DC2\EOT\152\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT=\STX\STX\ENQ\DC2\EOT\152\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT=\STX\STX\SOH\DC2\EOT\152\ACK\DC4#\n\
\\r\n\
\\ENQ\EOT=\STX\STX\ETX\DC2\EOT\152\ACK&'\n\
\\r\n\
\\ENQ\EOT=\STX\STX\b\DC2\EOT\152\ACK(5\n\
\\r\n\
\\ENQ\EOT=\STX\STX\a\DC2\EOT\152\ACK34\n\
\\f\n\
\\EOT\EOT=\STX\ETX\DC2\EOT\153\ACK\EOT*\n\
\\r\n\
\\ENQ\EOT=\STX\ETX\EOT\DC2\EOT\153\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT=\STX\ETX\ACK\DC2\EOT\153\ACK\r\EM\n\
\\r\n\
\\ENQ\EOT=\STX\ETX\SOH\DC2\EOT\153\ACK\SUB&\n\
\\r\n\
\\ENQ\EOT=\STX\ETX\ETX\DC2\EOT\153\ACK()\n\
\\f\n\
\\EOT\EOT=\STX\EOT\DC2\EOT\154\ACK\EOT&\n\
\\r\n\
\\ENQ\EOT=\STX\EOT\EOT\DC2\EOT\154\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT=\STX\EOT\ACK\DC2\EOT\154\ACK\r\SYN\n\
\\r\n\
\\ENQ\EOT=\STX\EOT\SOH\DC2\EOT\154\ACK\ETB!\n\
\\r\n\
\\ENQ\EOT=\STX\EOT\ETX\DC2\EOT\154\ACK$%\n\
\\f\n\
\\STX\EOT>\DC2\ACK\157\ACK\NUL\163\ACK\SOH\n\
\\v\n\
\\ETX\EOT>\SOH\DC2\EOT\157\ACK\b+\n\
\\f\n\
\\EOT\EOT>\STX\NUL\DC2\EOT\158\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT>\STX\NUL\EOT\DC2\EOT\158\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT>\STX\NUL\ENQ\DC2\EOT\158\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT>\STX\NUL\SOH\DC2\EOT\158\ACK\DC4\RS\n\
\\r\n\
\\ENQ\EOT>\STX\NUL\ETX\DC2\EOT\158\ACK!\"\n\
\\f\n\
\\EOT\EOT>\STX\SOH\DC2\EOT\159\ACK\EOT7\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\EOT\DC2\EOT\159\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\ENQ\DC2\EOT\159\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\SOH\DC2\EOT\159\ACK\DC4$\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\ETX\DC2\EOT\159\ACK'(\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\b\DC2\EOT\159\ACK)6\n\
\\r\n\
\\ENQ\EOT>\STX\SOH\a\DC2\EOT\159\ACK45\n\
\\f\n\
\\EOT\EOT>\STX\STX\DC2\EOT\160\ACK\EOT6\n\
\\r\n\
\\ENQ\EOT>\STX\STX\EOT\DC2\EOT\160\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT>\STX\STX\ENQ\DC2\EOT\160\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT>\STX\STX\SOH\DC2\EOT\160\ACK\DC4#\n\
\\r\n\
\\ENQ\EOT>\STX\STX\ETX\DC2\EOT\160\ACK&'\n\
\\r\n\
\\ENQ\EOT>\STX\STX\b\DC2\EOT\160\ACK(5\n\
\\r\n\
\\ENQ\EOT>\STX\STX\a\DC2\EOT\160\ACK34\n\
\\f\n\
\\EOT\EOT>\STX\ETX\DC2\EOT\161\ACK\EOT#\n\
\\r\n\
\\ENQ\EOT>\STX\ETX\EOT\DC2\EOT\161\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT>\STX\ETX\ACK\DC2\EOT\161\ACK\r\CAN\n\
\\r\n\
\\ENQ\EOT>\STX\ETX\SOH\DC2\EOT\161\ACK\EM\RS\n\
\\r\n\
\\ENQ\EOT>\STX\ETX\ETX\DC2\EOT\161\ACK!\"\n\
\\f\n\
\\EOT\EOT>\STX\EOT\DC2\EOT\162\ACK\EOT \n\
\\r\n\
\\ENQ\EOT>\STX\EOT\EOT\DC2\EOT\162\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT>\STX\EOT\ENQ\DC2\EOT\162\ACK\r\DC3\n\
\\r\n\
\\ENQ\EOT>\STX\EOT\SOH\DC2\EOT\162\ACK\DC4\ESC\n\
\\r\n\
\\ENQ\EOT>\STX\EOT\ETX\DC2\EOT\162\ACK\RS\US\n\
\\f\n\
\\STX\EOT?\DC2\ACK\165\ACK\NUL\194\a\SOH\n\
\\v\n\
\\ETX\EOT?\SOH\DC2\EOT\165\ACK\b\DC3\n\
\\SO\n\
\\EOT\EOT?\EOT\NUL\DC2\ACK\166\ACK\EOT\248\ACK\ENQ\n\
\\r\n\
\\ENQ\EOT?\EOT\NUL\SOH\DC2\EOT\166\ACK\t\r\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\NUL\DC2\EOT\167\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\NUL\SOH\DC2\EOT\167\ACK\b\SI\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\NUL\STX\DC2\EOT\167\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\SOH\DC2\EOT\168\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SOH\SOH\DC2\EOT\168\ACK\b\DC1\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SOH\STX\DC2\EOT\168\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\STX\DC2\EOT\169\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\STX\SOH\DC2\EOT\169\ACK\b\DC1\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\STX\STX\DC2\EOT\169\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\ETX\DC2\EOT\171\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ETX\SOH\DC2\EOT\171\ACK\b\DLE\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ETX\STX\DC2\EOT\171\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\EOT\DC2\EOT\173\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\EOT\SOH\DC2\EOT\173\ACK\b\f\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\EOT\STX\DC2\EOT\173\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\ENQ\DC2\EOT\174\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ENQ\SOH\DC2\EOT\174\ACK\b\DC4\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ENQ\STX\DC2\EOT\174\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\ACK\DC2\EOT\175\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ACK\SOH\DC2\EOT\175\ACK\b\DC2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ACK\STX\DC2\EOT\175\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\a\DC2\EOT\177\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\a\SOH\DC2\EOT\177\ACK\b\SI\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\a\STX\DC2\EOT\177\ACK\SYN\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\b\DC2\EOT\178\ACK\b\EM\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\b\SOH\DC2\EOT\178\ACK\b\v\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\b\STX\DC2\EOT\178\ACK\SYN\CAN\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\t\DC2\EOT\179\ACK\b\EM\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\t\SOH\DC2\EOT\179\ACK\b\f\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\t\STX\DC2\EOT\179\ACK\SYN\CAN\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\n\
\\DC2\EOT\181\ACK\b\EM\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\n\
\\SOH\DC2\EOT\181\ACK\b\DC3\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\n\
\\STX\DC2\EOT\181\ACK\SYN\CAN\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\v\DC2\EOT\183\ACK\b\EM\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\v\SOH\DC2\EOT\183\ACK\b\SI\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\v\STX\DC2\EOT\183\ACK\SYN\CAN\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\f\DC2\EOT\184\ACK\b\EM\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\f\SOH\DC2\EOT\184\ACK\b\r\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\f\STX\DC2\EOT\184\ACK\SYN\CAN\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\r\DC2\EOT\186\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\r\SOH\DC2\EOT\186\ACK\b\SYN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\r\STX\DC2\EOT\186\ACK\EM\ESC\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\SO\DC2\EOT\187\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SO\SOH\DC2\EOT\187\ACK\b\SYN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SO\STX\DC2\EOT\187\ACK\EM\ESC\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\SI\DC2\EOT\189\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SI\SOH\DC2\EOT\189\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SI\STX\DC2\EOT\189\ACK\ESC\GS\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\DLE\DC2\EOT\191\ACK\b\DC2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DLE\SOH\DC2\EOT\191\ACK\b\f\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DLE\STX\DC2\EOT\191\ACK\SI\DC1\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\DC1\DC2\EOT\192\ACK\b\DC2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC1\SOH\DC2\EOT\192\ACK\b\f\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC1\STX\DC2\EOT\192\ACK\SI\DC1\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\DC2\DC2\EOT\194\ACK\b/\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC2\SOH\DC2\EOT\194\ACK\b)\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC2\STX\DC2\EOT\194\ACK,.\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\DC3\DC2\EOT\196\ACK\b,\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC3\SOH\DC2\EOT\196\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC3\STX\DC2\EOT\196\ACK)+\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\DC4\DC2\EOT\197\ACK\b,\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC4\SOH\DC2\EOT\197\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\DC4\STX\DC2\EOT\197\ACK)+\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\NAK\DC2\EOT\199\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\NAK\SOH\DC2\EOT\199\ACK\b\SO\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\NAK\STX\DC2\EOT\199\ACK\ESC\GS\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\SYN\DC2\EOT\200\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SYN\SOH\DC2\EOT\200\ACK\b\ETB\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SYN\STX\DC2\EOT\200\ACK\ESC\GS\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\ETB\DC2\EOT\202\ACK\b#\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ETB\SOH\DC2\EOT\202\ACK\b\SYN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ETB\STX\DC2\EOT\202\ACK \"\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\CAN\DC2\EOT\203\ACK\b(\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\CAN\SOH\DC2\EOT\203\ACK\b\US\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\CAN\STX\DC2\EOT\203\ACK%'\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\EM\DC2\EOT\205\ACK\b\"\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\EM\SOH\DC2\EOT\205\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\EM\STX\DC2\EOT\205\ACK\US!\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\SUB\DC2\EOT\207\ACK\b\DC2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SUB\SOH\DC2\EOT\207\ACK\b\f\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\SUB\STX\DC2\EOT\207\ACK\SI\DC1\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\ESC\DC2\EOT\209\ACK\b!\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ESC\SOH\DC2\EOT\209\ACK\b\ESC\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\ESC\STX\DC2\EOT\209\ACK\RS \n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\FS\DC2\EOT\210\ACK\b*\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\FS\SOH\DC2\EOT\210\ACK\b$\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\FS\STX\DC2\EOT\210\ACK')\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\GS\DC2\EOT\212\ACK\b$\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\GS\SOH\DC2\EOT\212\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\GS\STX\DC2\EOT\212\ACK!#\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\RS\DC2\EOT\215\ACK\b1\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\RS\SOH\DC2\EOT\215\ACK\b\US\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\RS\STX\DC2\EOT\215\ACK.0\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\US\DC2\EOT\216\ACK\b2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\US\SOH\DC2\EOT\216\ACK\b(\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\US\STX\DC2\EOT\216\ACK/1\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX \DC2\EOT\218\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX \SOH\DC2\EOT\218\ACK\b\DC2\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX \STX\DC2\EOT\218\ACK\NAK\ETB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX!\DC2\EOT\219\ACK\b!\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX!\SOH\DC2\EOT\219\ACK\b\ESC\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX!\STX\DC2\EOT\219\ACK\RS \n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX\"\DC2\EOT\221\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\"\SOH\DC2\EOT\221\ACK\b\SYN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX\"\STX\DC2\EOT\221\ACK\EM\ESC\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX#\DC2\EOT\222\ACK\b\ESC\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX#\SOH\DC2\EOT\222\ACK\b\NAK\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX#\STX\DC2\EOT\222\ACK\CAN\SUB\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX$\DC2\EOT\224\ACK\b\SUB\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX$\SOH\DC2\EOT\224\ACK\b\DC4\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX$\STX\DC2\EOT\224\ACK\ETB\EM\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX%\DC2\EOT\226\ACK\b\"\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX%\SOH\DC2\EOT\226\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX%\STX\DC2\EOT\226\ACK\US!\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX&\DC2\EOT\227\ACK\b+\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX&\SOH\DC2\EOT\227\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX&\STX\DC2\EOT\227\ACK(*\n\
\%\n\
\\ACK\EOT?\EOT\NUL\STX'\DC2\EOT\230\ACK\b\NAK\SUB\NAK transaction related\n\
\\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX'\SOH\DC2\EOT\230\ACK\b\SI\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX'\STX\DC2\EOT\230\ACK\DC2\DC4\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX(\DC2\EOT\231\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX(\SOH\DC2\EOT\231\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX(\STX\DC2\EOT\231\ACK\ESC\GS\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX)\DC2\EOT\233\ACK\b\"\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX)\SOH\DC2\EOT\233\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX)\STX\DC2\EOT\233\ACK\US!\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX*\DC2\EOT\234\ACK\b+\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX*\SOH\DC2\EOT\234\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX*\STX\DC2\EOT\234\ACK(*\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX+\DC2\EOT\236\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX+\SOH\DC2\EOT\236\ACK\b\US\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX+\STX\DC2\EOT\236\ACK\"$\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX,\DC2\EOT\237\ACK\b.\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX,\SOH\DC2\EOT\237\ACK\b(\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX,\STX\DC2\EOT\237\ACK+-\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX-\DC2\EOT\239\ACK\b\NAK\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX-\SOH\DC2\EOT\239\ACK\b\SI\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX-\STX\DC2\EOT\239\ACK\DC2\DC4\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX.\DC2\EOT\240\ACK\b\RS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX.\SOH\DC2\EOT\240\ACK\b\CAN\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX.\STX\DC2\EOT\240\ACK\ESC\GS\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX/\DC2\EOT\242\ACK\b\"\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX/\SOH\DC2\EOT\242\ACK\b\FS\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX/\STX\DC2\EOT\242\ACK\US!\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX0\DC2\EOT\243\ACK\b+\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX0\SOH\DC2\EOT\243\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX0\STX\DC2\EOT\243\ACK(*\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX1\DC2\EOT\245\ACK\b%\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX1\SOH\DC2\EOT\245\ACK\b\US\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX1\STX\DC2\EOT\245\ACK\"$\n\
\\SO\n\
\\ACK\EOT?\EOT\NUL\STX2\DC2\EOT\246\ACK\b.\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX2\SOH\DC2\EOT\246\ACK\b(\n\
\\SI\n\
\\a\EOT?\EOT\NUL\STX2\STX\DC2\EOT\246\ACK+-\n\
\\f\n\
\\EOT\EOT?\STX\NUL\DC2\EOT\251\ACK\EOT\ESC\n\
\\r\n\
\\ENQ\EOT?\STX\NUL\EOT\DC2\EOT\251\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\NUL\ACK\DC2\EOT\251\ACK\r\DC1\n\
\\r\n\
\\ENQ\EOT?\STX\NUL\SOH\DC2\EOT\251\ACK\DC2\SYN\n\
\\r\n\
\\ENQ\EOT?\STX\NUL\ETX\DC2\EOT\251\ACK\EM\SUB\n\
\\f\n\
\\EOT\EOT?\STX\SOH\DC2\EOT\253\ACK\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\SOH\EOT\DC2\EOT\253\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\SOH\ACK\DC2\EOT\253\ACK\r\ESC\n\
\\r\n\
\\ENQ\EOT?\STX\SOH\SOH\DC2\EOT\253\ACK\FS#\n\
\\r\n\
\\ENQ\EOT?\STX\SOH\ETX\DC2\EOT\253\ACK/0\n\
\\f\n\
\\EOT\EOT?\STX\STX\DC2\EOT\254\ACK\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\STX\EOT\DC2\EOT\254\ACK\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\STX\ACK\DC2\EOT\254\ACK\r\GS\n\
\\r\n\
\\ENQ\EOT?\STX\STX\SOH\DC2\EOT\254\ACK\RS'\n\
\\r\n\
\\ENQ\EOT?\STX\STX\ETX\DC2\EOT\254\ACK/0\n\
\\f\n\
\\EOT\EOT?\STX\ETX\DC2\EOT\128\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\ETX\EOT\DC2\EOT\128\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\ETX\ACK\DC2\EOT\128\a\r\GS\n\
\\r\n\
\\ENQ\EOT?\STX\ETX\SOH\DC2\EOT\128\a\RS'\n\
\\r\n\
\\ENQ\EOT?\STX\ETX\ETX\DC2\EOT\128\a/0\n\
\\f\n\
\\EOT\EOT?\STX\EOT\DC2\EOT\129\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\EOT\EOT\DC2\EOT\129\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\EOT\ACK\DC2\EOT\129\a\r\FS\n\
\\r\n\
\\ENQ\EOT?\STX\EOT\SOH\DC2\EOT\129\a\GS%\n\
\\r\n\
\\ENQ\EOT?\STX\EOT\ETX\DC2\EOT\129\a/0\n\
\\f\n\
\\EOT\EOT?\STX\ENQ\DC2\EOT\130\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\ENQ\EOT\DC2\EOT\130\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\ENQ\ACK\DC2\EOT\130\a\r\CAN\n\
\\r\n\
\\ENQ\EOT?\STX\ENQ\SOH\DC2\EOT\130\a\EM\GS\n\
\\r\n\
\\ENQ\EOT?\STX\ENQ\ETX\DC2\EOT\130\a/0\n\
\\f\n\
\\EOT\EOT?\STX\ACK\DC2\EOT\131\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\ACK\EOT\DC2\EOT\131\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\ACK\ACK\DC2\EOT\131\a\r\US\n\
\\r\n\
\\ENQ\EOT?\STX\ACK\SOH\DC2\EOT\131\a ,\n\
\\r\n\
\\ENQ\EOT?\STX\ACK\ETX\DC2\EOT\131\a/0\n\
\\f\n\
\\EOT\EOT?\STX\a\DC2\EOT\132\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\a\EOT\DC2\EOT\132\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\a\ACK\DC2\EOT\132\a\r\GS\n\
\\r\n\
\\ENQ\EOT?\STX\a\SOH\DC2\EOT\132\a\RS(\n\
\\r\n\
\\ENQ\EOT?\STX\a\ETX\DC2\EOT\132\a/0\n\
\\f\n\
\\EOT\EOT?\STX\b\DC2\EOT\133\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX\b\EOT\DC2\EOT\133\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\b\ACK\DC2\EOT\133\a\r\ESC\n\
\\r\n\
\\ENQ\EOT?\STX\b\SOH\DC2\EOT\133\a\FS#\n\
\\r\n\
\\ENQ\EOT?\STX\b\ETX\DC2\EOT\133\a/0\n\
\\f\n\
\\EOT\EOT?\STX\t\DC2\EOT\134\a\EOT2\n\
\\r\n\
\\ENQ\EOT?\STX\t\EOT\DC2\EOT\134\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\t\ACK\DC2\EOT\134\a\r\ETB\n\
\\r\n\
\\ENQ\EOT?\STX\t\SOH\DC2\EOT\134\a\CAN\ESC\n\
\\r\n\
\\ENQ\EOT?\STX\t\ETX\DC2\EOT\134\a/1\n\
\\f\n\
\\EOT\EOT?\STX\n\
\\DC2\EOT\135\a\EOT2\n\
\\r\n\
\\ENQ\EOT?\STX\n\
\\EOT\DC2\EOT\135\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\n\
\\ACK\DC2\EOT\135\a\r\CAN\n\
\\r\n\
\\ENQ\EOT?\STX\n\
\\SOH\DC2\EOT\135\a\EM\GS\n\
\\r\n\
\\ENQ\EOT?\STX\n\
\\ETX\DC2\EOT\135\a/1\n\
\\f\n\
\\EOT\EOT?\STX\v\DC2\EOT\136\a\EOT2\n\
\\r\n\
\\ENQ\EOT?\STX\v\EOT\DC2\EOT\136\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\v\ACK\DC2\EOT\136\a\r\US\n\
\\r\n\
\\ENQ\EOT?\STX\v\SOH\DC2\EOT\136\a +\n\
\\r\n\
\\ENQ\EOT?\STX\v\ETX\DC2\EOT\136\a/1\n\
\\f\n\
\\EOT\EOT?\STX\f\DC2\EOT\138\a\EOT2\n\
\\r\n\
\\ENQ\EOT?\STX\f\EOT\DC2\EOT\138\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\f\ACK\DC2\EOT\138\a\r\ESC\n\
\\r\n\
\\ENQ\EOT?\STX\f\SOH\DC2\EOT\138\a\FS#\n\
\\r\n\
\\ENQ\EOT?\STX\f\ETX\DC2\EOT\138\a/1\n\
\\f\n\
\\EOT\EOT?\STX\r\DC2\EOT\139\a\EOT2\n\
\\r\n\
\\ENQ\EOT?\STX\r\EOT\DC2\EOT\139\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\r\ACK\DC2\EOT\139\a\r\EM\n\
\\r\n\
\\ENQ\EOT?\STX\r\SOH\DC2\EOT\139\a\SUB\US\n\
\\r\n\
\\ENQ\EOT?\STX\r\ETX\DC2\EOT\139\a/1\n\
\\f\n\
\\EOT\EOT?\STX\SO\DC2\EOT\141\a\EOT6\n\
\\r\n\
\\ENQ\EOT?\STX\SO\EOT\DC2\EOT\141\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\SO\ACK\DC2\EOT\141\a\r!\n\
\\r\n\
\\ENQ\EOT?\STX\SO\SOH\DC2\EOT\141\a\"0\n\
\\r\n\
\\ENQ\EOT?\STX\SO\ETX\DC2\EOT\141\a35\n\
\\f\n\
\\EOT\EOT?\STX\SI\DC2\EOT\142\a\EOT6\n\
\\r\n\
\\ENQ\EOT?\STX\SI\EOT\DC2\EOT\142\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\SI\ACK\DC2\EOT\142\a\r!\n\
\\r\n\
\\ENQ\EOT?\STX\SI\SOH\DC2\EOT\142\a\"0\n\
\\r\n\
\\ENQ\EOT?\STX\SI\ETX\DC2\EOT\142\a35\n\
\\f\n\
\\EOT\EOT?\STX\DLE\DC2\EOT\144\a\EOT:\n\
\\r\n\
\\ENQ\EOT?\STX\DLE\EOT\DC2\EOT\144\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\DLE\ACK\DC2\EOT\144\a\r#\n\
\\r\n\
\\ENQ\EOT?\STX\DLE\SOH\DC2\EOT\144\a$4\n\
\\r\n\
\\ENQ\EOT?\STX\DLE\ETX\DC2\EOT\144\a79\n\
\\f\n\
\\EOT\EOT?\STX\DC1\DC2\EOT\145\a\EOT#\n\
\\r\n\
\\ENQ\EOT?\STX\DC1\EOT\DC2\EOT\145\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\DC1\ACK\DC2\EOT\145\a\r\CAN\n\
\\r\n\
\\ENQ\EOT?\STX\DC1\SOH\DC2\EOT\145\a\EM\GS\n\
\\r\n\
\\ENQ\EOT?\STX\DC1\ETX\DC2\EOT\145\a \"\n\
\\f\n\
\\EOT\EOT?\STX\DC2\DC2\EOT\146\a\EOT#\n\
\\r\n\
\\ENQ\EOT?\STX\DC2\EOT\DC2\EOT\146\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\DC2\ACK\DC2\EOT\146\a\r\CAN\n\
\\r\n\
\\ENQ\EOT?\STX\DC2\SOH\DC2\EOT\146\a\EM\GS\n\
\\r\n\
\\ENQ\EOT?\STX\DC2\ETX\DC2\EOT\146\a \"\n\
\\f\n\
\\EOT\EOT?\STX\DC3\DC2\EOT\147\a\EOTY\n\
\\r\n\
\\ENQ\EOT?\STX\DC3\EOT\DC2\EOT\147\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\DC3\ACK\DC2\EOT\147\a\r3\n\
\\r\n\
\\ENQ\EOT?\STX\DC3\SOH\DC2\EOT\147\a4S\n\
\\r\n\
\\ENQ\EOT?\STX\DC3\ETX\DC2\EOT\147\aVX\n\
\\f\n\
\\EOT\EOT?\STX\DC4\DC2\EOT\149\a\EOTU\n\
\\r\n\
\\ENQ\EOT?\STX\DC4\EOT\DC2\EOT\149\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\DC4\ACK\DC2\EOT\149\a\r,\n\
\\r\n\
\\ENQ\EOT?\STX\DC4\SOH\DC2\EOT\149\a.?\n\
\\r\n\
\\ENQ\EOT?\STX\DC4\ETX\DC2\EOT\149\aRT\n\
\\f\n\
\\EOT\EOT?\STX\NAK\DC2\EOT\150\a\EOTU\n\
\\r\n\
\\ENQ\EOT?\STX\NAK\EOT\DC2\EOT\150\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\NAK\ACK\DC2\EOT\150\a\r4\n\
\\r\n\
\\ENQ\EOT?\STX\NAK\SOH\DC2\EOT\150\a5N\n\
\\r\n\
\\ENQ\EOT?\STX\NAK\ETX\DC2\EOT\150\aRT\n\
\\f\n\
\\EOT\EOT?\STX\SYN\DC2\EOT\152\a\EOTD\n\
\\r\n\
\\ENQ\EOT?\STX\SYN\EOT\DC2\EOT\152\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\SYN\ACK\DC2\EOT\152\a\r\US\n\
\\r\n\
\\ENQ\EOT?\STX\SYN\SOH\DC2\EOT\152\a +\n\
\\r\n\
\\ENQ\EOT?\STX\SYN\ETX\DC2\EOT\152\aAC\n\
\\f\n\
\\EOT\EOT?\STX\ETB\DC2\EOT\153\a\EOTD\n\
\\r\n\
\\ENQ\EOT?\STX\ETB\EOT\DC2\EOT\153\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\ETB\ACK\DC2\EOT\153\a\r'\n\
\\r\n\
\\ENQ\EOT?\STX\ETB\SOH\DC2\EOT\153\a(;\n\
\\r\n\
\\ENQ\EOT?\STX\ETB\ETX\DC2\EOT\153\aAC\n\
\\f\n\
\\EOT\EOT?\STX\CAN\DC2\EOT\155\a\EOTM\n\
\\r\n\
\\ENQ\EOT?\STX\CAN\EOT\DC2\EOT\155\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\CAN\ACK\DC2\EOT\155\a\r!\n\
\\r\n\
\\ENQ\EOT?\STX\CAN\SOH\DC2\EOT\155\a\"/\n\
\\r\n\
\\ENQ\EOT?\STX\CAN\ETX\DC2\EOT\155\aJL\n\
\\f\n\
\\EOT\EOT?\STX\EM\DC2\EOT\156\a\EOTM\n\
\\r\n\
\\ENQ\EOT?\STX\EM\EOT\DC2\EOT\156\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\EM\ACK\DC2\EOT\156\a\r)\n\
\\r\n\
\\ENQ\EOT?\STX\EM\SOH\DC2\EOT\156\a*?\n\
\\r\n\
\\ENQ\EOT?\STX\EM\ETX\DC2\EOT\156\aJL\n\
\\f\n\
\\EOT\EOT?\STX\SUB\DC2\EOT\158\a\EOT>\n\
\\r\n\
\\ENQ\EOT?\STX\SUB\EOT\DC2\EOT\158\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\SUB\ACK\DC2\EOT\158\a\r%\n\
\\r\n\
\\ENQ\EOT?\STX\SUB\SOH\DC2\EOT\158\a&7\n\
\\r\n\
\\ENQ\EOT?\STX\SUB\ETX\DC2\EOT\158\a;=\n\
\\f\n\
\\EOT\EOT?\STX\ESC\DC2\EOT\160\a\EOT#\n\
\\r\n\
\\ENQ\EOT?\STX\ESC\EOT\DC2\EOT\160\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\ESC\ACK\DC2\EOT\160\a\r\CAN\n\
\\r\n\
\\ENQ\EOT?\STX\ESC\SOH\DC2\EOT\160\a\EM\GS\n\
\\r\n\
\\ENQ\EOT?\STX\ESC\ETX\DC2\EOT\160\a \"\n\
\\f\n\
\\EOT\EOT?\STX\FS\DC2\EOT\162\a\EOT;\n\
\\r\n\
\\ENQ\EOT?\STX\FS\EOT\DC2\EOT\162\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\FS\ACK\DC2\EOT\162\a\r$\n\
\\r\n\
\\ENQ\EOT?\STX\FS\SOH\DC2\EOT\162\a%5\n\
\\r\n\
\\ENQ\EOT?\STX\FS\ETX\DC2\EOT\162\a8:\n\
\\f\n\
\\EOT\EOT?\STX\GS\DC2\EOT\163\a\EOTK\n\
\\r\n\
\\ENQ\EOT?\STX\GS\EOT\DC2\EOT\163\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\GS\ACK\DC2\EOT\163\a\r,\n\
\\r\n\
\\ENQ\EOT?\STX\GS\SOH\DC2\EOT\163\a-E\n\
\\r\n\
\\ENQ\EOT?\STX\GS\ETX\DC2\EOT\163\aHJ\n\
\\f\n\
\\EOT\EOT?\STX\RS\DC2\EOT\165\a\EOTE\n\
\\r\n\
\\ENQ\EOT?\STX\RS\EOT\DC2\EOT\165\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\RS\ACK\DC2\EOT\165\a\r(\n\
\\r\n\
\\ENQ\EOT?\STX\RS\SOH\DC2\EOT\165\a)?\n\
\\r\n\
\\ENQ\EOT?\STX\RS\ETX\DC2\EOT\165\aBD\n\
\\f\n\
\\EOT\EOT?\STX\US\DC2\EOT\167\a\EOTC\n\
\\r\n\
\\ENQ\EOT?\STX\US\EOT\DC2\EOT\167\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\US\ACK\DC2\EOT\167\a\r(\n\
\\r\n\
\\ENQ\EOT?\STX\US\SOH\DC2\EOT\167\a)=\n\
\\r\n\
\\ENQ\EOT?\STX\US\ETX\DC2\EOT\167\a@B\n\
\\f\n\
\\EOT\EOT?\STX \DC2\EOT\168\a\EOTS\n\
\\r\n\
\\ENQ\EOT?\STX \EOT\DC2\EOT\168\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX \ACK\DC2\EOT\168\a\r0\n\
\\r\n\
\\ENQ\EOT?\STX \SOH\DC2\EOT\168\a1M\n\
\\r\n\
\\ENQ\EOT?\STX \ETX\DC2\EOT\168\aPR\n\
\\f\n\
\\EOT\EOT?\STX!\DC2\EOT\170\a\EOT-\n\
\\r\n\
\\ENQ\EOT?\STX!\EOT\DC2\EOT\170\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX!\ACK\DC2\EOT\170\a\r\GS\n\
\\r\n\
\\ENQ\EOT?\STX!\SOH\DC2\EOT\170\a\RS'\n\
\\r\n\
\\ENQ\EOT?\STX!\ETX\DC2\EOT\170\a*,\n\
\\f\n\
\\EOT\EOT?\STX\"\DC2\EOT\171\a\EOT=\n\
\\r\n\
\\ENQ\EOT?\STX\"\EOT\DC2\EOT\171\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX\"\ACK\DC2\EOT\171\a\r%\n\
\\r\n\
\\ENQ\EOT?\STX\"\SOH\DC2\EOT\171\a&7\n\
\\r\n\
\\ENQ\EOT?\STX\"\ETX\DC2\EOT\171\a:<\n\
\\f\n\
\\EOT\EOT?\STX#\DC2\EOT\173\a\EOT5\n\
\\r\n\
\\ENQ\EOT?\STX#\EOT\DC2\EOT\173\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX#\ACK\DC2\EOT\173\a\r!\n\
\\r\n\
\\ENQ\EOT?\STX#\SOH\DC2\EOT\173\a\"/\n\
\\r\n\
\\ENQ\EOT?\STX#\ETX\DC2\EOT\173\a24\n\
\\f\n\
\\EOT\EOT?\STX$\DC2\EOT\174\a\EOT3\n\
\\r\n\
\\ENQ\EOT?\STX$\EOT\DC2\EOT\174\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX$\ACK\DC2\EOT\174\a\r \n\
\\r\n\
\\ENQ\EOT?\STX$\SOH\DC2\EOT\174\a!-\n\
\\r\n\
\\ENQ\EOT?\STX$\ETX\DC2\EOT\174\a02\n\
\\f\n\
\\EOT\EOT?\STX%\DC2\EOT\176\a\EOT1\n\
\\r\n\
\\ENQ\EOT?\STX%\EOT\DC2\EOT\176\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX%\ACK\DC2\EOT\176\a\r\US\n\
\\r\n\
\\ENQ\EOT?\STX%\SOH\DC2\EOT\176\a +\n\
\\r\n\
\\ENQ\EOT?\STX%\ETX\DC2\EOT\176\a.0\n\
\\f\n\
\\EOT\EOT?\STX&\DC2\EOT\178\a\EOT=\n\
\\r\n\
\\ENQ\EOT?\STX&\EOT\DC2\EOT\178\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX&\ACK\DC2\EOT\178\a\r%\n\
\\r\n\
\\ENQ\EOT?\STX&\SOH\DC2\EOT\178\a&7\n\
\\r\n\
\\ENQ\EOT?\STX&\ETX\DC2\EOT\178\a:<\n\
\\f\n\
\\EOT\EOT?\STX'\DC2\EOT\179\a\EOTM\n\
\\r\n\
\\ENQ\EOT?\STX'\EOT\DC2\EOT\179\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX'\ACK\DC2\EOT\179\a\r-\n\
\\r\n\
\\ENQ\EOT?\STX'\SOH\DC2\EOT\179\a.G\n\
\\r\n\
\\ENQ\EOT?\STX'\ETX\DC2\EOT\179\aJL\n\
\#\n\
\\EOT\EOT?\STX(\DC2\EOT\182\a\EOT'\SUB\NAK transaction related\n\
\\n\
\\r\n\
\\ENQ\EOT?\STX(\EOT\DC2\EOT\182\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX(\ACK\DC2\EOT\182\a\r\SUB\n\
\\r\n\
\\ENQ\EOT?\STX(\SOH\DC2\EOT\182\a\ESC!\n\
\\r\n\
\\ENQ\EOT?\STX(\ETX\DC2\EOT\182\a$&\n\
\\f\n\
\\EOT\EOT?\STX)\DC2\EOT\183\a\EOT7\n\
\\r\n\
\\ENQ\EOT?\STX)\EOT\DC2\EOT\183\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX)\ACK\DC2\EOT\183\a\r\"\n\
\\r\n\
\\ENQ\EOT?\STX)\SOH\DC2\EOT\183\a#1\n\
\\r\n\
\\ENQ\EOT?\STX)\ETX\DC2\EOT\183\a46\n\
\\f\n\
\\EOT\EOT?\STX*\DC2\EOT\184\a\EOT<\n\
\\r\n\
\\ENQ\EOT?\STX*\EOT\DC2\EOT\184\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX*\ACK\DC2\EOT\184\a\r%\n\
\\r\n\
\\ENQ\EOT?\STX*\SOH\DC2\EOT\184\a&7\n\
\\r\n\
\\ENQ\EOT?\STX*\ETX\DC2\EOT\184\a9;\n\
\\f\n\
\\EOT\EOT?\STX+\DC2\EOT\185\a\EOTM\n\
\\r\n\
\\ENQ\EOT?\STX+\EOT\DC2\EOT\185\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX+\ACK\DC2\EOT\185\a\r-\n\
\\r\n\
\\ENQ\EOT?\STX+\SOH\DC2\EOT\185\a.G\n\
\\r\n\
\\ENQ\EOT?\STX+\ETX\DC2\EOT\185\aJL\n\
\\f\n\
\\EOT\EOT?\STX,\DC2\EOT\186\a\EOTC\n\
\\r\n\
\\ENQ\EOT?\STX,\EOT\DC2\EOT\186\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX,\ACK\DC2\EOT\186\a\r(\n\
\\r\n\
\\ENQ\EOT?\STX,\SOH\DC2\EOT\186\a)=\n\
\\r\n\
\\ENQ\EOT?\STX,\ETX\DC2\EOT\186\a@B\n\
\\f\n\
\\EOT\EOT?\STX-\DC2\EOT\187\a\EOTS\n\
\\r\n\
\\ENQ\EOT?\STX-\EOT\DC2\EOT\187\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX-\ACK\DC2\EOT\187\a\r0\n\
\\r\n\
\\ENQ\EOT?\STX-\SOH\DC2\EOT\187\a1M\n\
\\r\n\
\\ENQ\EOT?\STX-\ETX\DC2\EOT\187\aPR\n\
\\f\n\
\\EOT\EOT?\STX.\DC2\EOT\188\a\EOT'\n\
\\r\n\
\\ENQ\EOT?\STX.\EOT\DC2\EOT\188\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX.\ACK\DC2\EOT\188\a\r\SUB\n\
\\r\n\
\\ENQ\EOT?\STX.\SOH\DC2\EOT\188\a\ESC!\n\
\\r\n\
\\ENQ\EOT?\STX.\ETX\DC2\EOT\188\a$&\n\
\\f\n\
\\EOT\EOT?\STX/\DC2\EOT\189\a\EOT7\n\
\\r\n\
\\ENQ\EOT?\STX/\EOT\DC2\EOT\189\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX/\ACK\DC2\EOT\189\a\r\"\n\
\\r\n\
\\ENQ\EOT?\STX/\SOH\DC2\EOT\189\a#1\n\
\\r\n\
\\ENQ\EOT?\STX/\ETX\DC2\EOT\189\a46\n\
\\f\n\
\\EOT\EOT?\STX0\DC2\EOT\190\a\EOT=\n\
\\r\n\
\\ENQ\EOT?\STX0\EOT\DC2\EOT\190\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX0\ACK\DC2\EOT\190\a\r%\n\
\\r\n\
\\ENQ\EOT?\STX0\SOH\DC2\EOT\190\a&7\n\
\\r\n\
\\ENQ\EOT?\STX0\ETX\DC2\EOT\190\a:<\n\
\\f\n\
\\EOT\EOT?\STX1\DC2\EOT\191\a\EOTM\n\
\\r\n\
\\ENQ\EOT?\STX1\EOT\DC2\EOT\191\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX1\ACK\DC2\EOT\191\a\r-\n\
\\r\n\
\\ENQ\EOT?\STX1\SOH\DC2\EOT\191\a.G\n\
\\r\n\
\\ENQ\EOT?\STX1\ETX\DC2\EOT\191\aJL\n\
\\f\n\
\\EOT\EOT?\STX2\DC2\EOT\192\a\EOTC\n\
\\r\n\
\\ENQ\EOT?\STX2\EOT\DC2\EOT\192\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX2\ACK\DC2\EOT\192\a\r(\n\
\\r\n\
\\ENQ\EOT?\STX2\SOH\DC2\EOT\192\a)=\n\
\\r\n\
\\ENQ\EOT?\STX2\ETX\DC2\EOT\192\a@B\n\
\\f\n\
\\EOT\EOT?\STX3\DC2\EOT\193\a\EOTS\n\
\\r\n\
\\ENQ\EOT?\STX3\EOT\DC2\EOT\193\a\EOT\f\n\
\\r\n\
\\ENQ\EOT?\STX3\ACK\DC2\EOT\193\a\r0\n\
\\r\n\
\\ENQ\EOT?\STX3\SOH\DC2\EOT\193\a1M\n\
\\r\n\
\\ENQ\EOT?\STX3\ETX\DC2\EOT\193\aPR"