{-# LANGUAGE OverloadedStrings #-}

{- Defines commands using the generated protobuf datatypes -}
module Pulsar.Protocol.Commands where

import qualified Data.Binary                   as B
import           Data.ProtoLens                 ( defMessage )
import qualified Data.Text                     as T
import           Data.Version                   ( showVersion )
import           Lens.Family
import           Paths_supernova                ( version )
import           Proto.PulsarApi
import qualified Proto.PulsarApi_Fields        as F
import           Pulsar.Types

connect :: BaseCommand
connect :: BaseCommand
connect = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandConnect
forall (f :: * -> *) s a.
(Functor f, HasField s "connect" a) =>
LensLike' f s a
F.connect LensLike' Identity BaseCommand CommandConnect
-> CommandConnect -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandConnect
conn
 where
  conn :: CommandConnect
  conn :: CommandConnect
conn = CommandConnect
forall msg. Message msg => msg
defMessage
    CommandConnect
-> (CommandConnect -> CommandConnect) -> CommandConnect
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandConnect Text
forall (f :: * -> *) s a.
(Functor f, HasField s "clientVersion" a) =>
LensLike' f s a
F.clientVersion LensLike' Identity CommandConnect Text
-> Text -> CommandConnect -> CommandConnect
forall s t a b. ASetter s t a b -> b -> s -> t
.~ "Pulsar-Client-Haskell-v" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Version -> String
showVersion Version
version)
    CommandConnect
-> (CommandConnect -> CommandConnect) -> CommandConnect
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandConnect Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "protocolVersion" a) =>
LensLike' f s a
F.protocolVersion LensLike' Identity CommandConnect Int32
-> Int32 -> CommandConnect -> CommandConnect
forall s t a b. ASetter s t a b -> b -> s -> t
.~ 15

subType :: SubType -> CommandSubscribe'SubType
subType :: SubType -> CommandSubscribe'SubType
subType Exclusive = CommandSubscribe'SubType
CommandSubscribe'Exclusive
subType Shared    = CommandSubscribe'SubType
CommandSubscribe'Shared
subType Failover  = CommandSubscribe'SubType
CommandSubscribe'Failover
subType KeyShared = CommandSubscribe'SubType
CommandSubscribe'Key_Shared

subscribe :: B.Word64 -> B.Word64 -> Topic -> SubType -> SubName -> BaseCommand
subscribe :: Word64 -> Word64 -> Topic -> SubType -> SubName -> BaseCommand
subscribe req :: Word64
req cid :: Word64
cid topic :: Topic
topic stype :: SubType
stype (SubName sname :: Text
sname) = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'SUBSCRIBE
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandSubscribe
forall (f :: * -> *) s a.
(Functor f, HasField s "subscribe" a) =>
LensLike' f s a
F.subscribe LensLike' Identity BaseCommand CommandSubscribe
-> CommandSubscribe -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandSubscribe
subs
 where
  subs :: CommandSubscribe
  subs :: CommandSubscribe
subs = CommandSubscribe
forall msg. Message msg => msg
defMessage
    CommandSubscribe
-> (CommandSubscribe -> CommandSubscribe) -> CommandSubscribe
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSubscribe Text
forall (f :: * -> *) s a.
(Functor f, HasField s "topic" a) =>
LensLike' f s a
F.topic LensLike' Identity CommandSubscribe Text
-> Text -> CommandSubscribe -> CommandSubscribe
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String -> Text
T.pack (Topic -> String
forall a. Show a => a -> String
show Topic
topic)
    CommandSubscribe
-> (CommandSubscribe -> CommandSubscribe) -> CommandSubscribe
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSubscribe Text
forall (f :: * -> *) s a.
(Functor f, HasField s "subscription" a) =>
LensLike' f s a
F.subscription LensLike' Identity CommandSubscribe Text
-> Text -> CommandSubscribe -> CommandSubscribe
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
sname
    CommandSubscribe
-> (CommandSubscribe -> CommandSubscribe) -> CommandSubscribe
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSubscribe CommandSubscribe'SubType
forall (f :: * -> *) s a.
(Functor f, HasField s "subType" a) =>
LensLike' f s a
F.subType LensLike' Identity CommandSubscribe CommandSubscribe'SubType
-> CommandSubscribe'SubType -> CommandSubscribe -> CommandSubscribe
forall s t a b. ASetter s t a b -> b -> s -> t
.~ SubType -> CommandSubscribe'SubType
subType SubType
stype
    CommandSubscribe
-> (CommandSubscribe -> CommandSubscribe) -> CommandSubscribe
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSubscribe Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "consumerId" a) =>
LensLike' f s a
F.consumerId LensLike' Identity CommandSubscribe Word64
-> Word64 -> CommandSubscribe -> CommandSubscribe
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
cid
    CommandSubscribe
-> (CommandSubscribe -> CommandSubscribe) -> CommandSubscribe
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSubscribe Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "requestId" a) =>
LensLike' f s a
F.requestId LensLike' Identity CommandSubscribe Word64
-> Word64 -> CommandSubscribe -> CommandSubscribe
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
req

flow :: B.Word64 -> B.Word32 -> BaseCommand
flow :: Word64 -> Word32 -> BaseCommand
flow cid :: Word64
cid permits :: Word32
permits = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'FLOW
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandFlow
forall (f :: * -> *) s a.
(Functor f, HasField s "flow" a) =>
LensLike' f s a
F.flow LensLike' Identity BaseCommand CommandFlow
-> CommandFlow -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandFlow
flowCmd
 where
  flowCmd :: CommandFlow
  flowCmd :: CommandFlow
flowCmd = CommandFlow
forall msg. Message msg => msg
defMessage
    CommandFlow -> (CommandFlow -> CommandFlow) -> CommandFlow
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandFlow Word32
forall (f :: * -> *) s a.
(Functor f, HasField s "messagePermits" a) =>
LensLike' f s a
F.messagePermits LensLike' Identity CommandFlow Word32
-> Word32 -> CommandFlow -> CommandFlow
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word32
permits
    CommandFlow -> (CommandFlow -> CommandFlow) -> CommandFlow
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandFlow Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "consumerId" a) =>
LensLike' f s a
F.consumerId LensLike' Identity CommandFlow Word64
-> Word64 -> CommandFlow -> CommandFlow
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
cid

ack :: B.Word64 -> MessageIdData -> BaseCommand
ack :: Word64 -> MessageIdData -> BaseCommand
ack cid :: Word64
cid msgId :: MessageIdData
msgId = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'ACK
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandAck
forall (f :: * -> *) s a.
(Functor f, HasField s "ack" a) =>
LensLike' f s a
F.ack LensLike' Identity BaseCommand CommandAck
-> CommandAck -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandAck
ackCmd
 where
  ackCmd :: CommandAck
  ackCmd :: CommandAck
ackCmd = CommandAck
forall msg. Message msg => msg
defMessage
    CommandAck -> (CommandAck -> CommandAck) -> CommandAck
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandAck [MessageIdData]
forall (f :: * -> *) s a.
(Functor f, HasField s "messageId" a) =>
LensLike' f s a
F.messageId LensLike' Identity CommandAck [MessageIdData]
-> [MessageIdData] -> CommandAck -> CommandAck
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ MessageIdData
msgId ]
    CommandAck -> (CommandAck -> CommandAck) -> CommandAck
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandAck Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "consumerId" a) =>
LensLike' f s a
F.consumerId LensLike' Identity CommandAck Word64
-> Word64 -> CommandAck -> CommandAck
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
cid

closeConsumer :: B.Word64 -> B.Word64 -> BaseCommand
closeConsumer :: Word64 -> Word64 -> BaseCommand
closeConsumer req :: Word64
req cid :: Word64
cid = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'CLOSE_CONSUMER
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandCloseConsumer
forall (f :: * -> *) s a.
(Functor f, HasField s "closeConsumer" a) =>
LensLike' f s a
F.closeConsumer LensLike' Identity BaseCommand CommandCloseConsumer
-> CommandCloseConsumer -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandCloseConsumer
close
 where
  close :: CommandCloseConsumer
  close :: CommandCloseConsumer
close = CommandCloseConsumer
forall msg. Message msg => msg
defMessage
    CommandCloseConsumer
-> (CommandCloseConsumer -> CommandCloseConsumer)
-> CommandCloseConsumer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandCloseConsumer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "consumerId" a) =>
LensLike' f s a
F.consumerId LensLike' Identity CommandCloseConsumer Word64
-> Word64 -> CommandCloseConsumer -> CommandCloseConsumer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
cid
    CommandCloseConsumer
-> (CommandCloseConsumer -> CommandCloseConsumer)
-> CommandCloseConsumer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandCloseConsumer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "requestId" a) =>
LensLike' f s a
F.requestId LensLike' Identity CommandCloseConsumer Word64
-> Word64 -> CommandCloseConsumer -> CommandCloseConsumer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
req

producer :: B.Word64 -> B.Word64 -> Topic -> BaseCommand
producer :: Word64 -> Word64 -> Topic -> BaseCommand
producer req :: Word64
req pid :: Word64
pid topic :: Topic
topic = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'PRODUCER
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandProducer
forall (f :: * -> *) s a.
(Functor f, HasField s "producer" a) =>
LensLike' f s a
F.producer LensLike' Identity BaseCommand CommandProducer
-> CommandProducer -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandProducer
prod
 where
  prod :: CommandProducer
  prod :: CommandProducer
prod = CommandProducer
forall msg. Message msg => msg
defMessage
    CommandProducer
-> (CommandProducer -> CommandProducer) -> CommandProducer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandProducer Text
forall (f :: * -> *) s a.
(Functor f, HasField s "topic" a) =>
LensLike' f s a
F.topic LensLike' Identity CommandProducer Text
-> Text -> CommandProducer -> CommandProducer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String -> Text
T.pack (Topic -> String
forall a. Show a => a -> String
show Topic
topic)
    CommandProducer
-> (CommandProducer -> CommandProducer) -> CommandProducer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandProducer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "producerId" a) =>
LensLike' f s a
F.producerId LensLike' Identity CommandProducer Word64
-> Word64 -> CommandProducer -> CommandProducer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
pid
    CommandProducer
-> (CommandProducer -> CommandProducer) -> CommandProducer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandProducer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "requestId" a) =>
LensLike' f s a
F.requestId LensLike' Identity CommandProducer Word64
-> Word64 -> CommandProducer -> CommandProducer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
req

closeProducer :: B.Word64 -> B.Word64 -> BaseCommand
closeProducer :: Word64 -> Word64 -> BaseCommand
closeProducer req :: Word64
req pid :: Word64
pid = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'CLOSE_PRODUCER
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandCloseProducer
forall (f :: * -> *) s a.
(Functor f, HasField s "closeProducer" a) =>
LensLike' f s a
F.closeProducer LensLike' Identity BaseCommand CommandCloseProducer
-> CommandCloseProducer -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandCloseProducer
prod
 where
  prod :: CommandCloseProducer
  prod :: CommandCloseProducer
prod = CommandCloseProducer
forall msg. Message msg => msg
defMessage
    CommandCloseProducer
-> (CommandCloseProducer -> CommandCloseProducer)
-> CommandCloseProducer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandCloseProducer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "producerId" a) =>
LensLike' f s a
F.producerId LensLike' Identity CommandCloseProducer Word64
-> Word64 -> CommandCloseProducer -> CommandCloseProducer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
pid
    CommandCloseProducer
-> (CommandCloseProducer -> CommandCloseProducer)
-> CommandCloseProducer
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandCloseProducer Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "requestId" a) =>
LensLike' f s a
F.requestId LensLike' Identity CommandCloseProducer Word64
-> Word64 -> CommandCloseProducer -> CommandCloseProducer
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
req

send :: B.Word64 -> B.Word64 -> BaseCommand
send :: Word64 -> Word64 -> BaseCommand
send pid :: Word64
pid sid :: Word64
sid = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'SEND
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandSend
forall (f :: * -> *) s a.
(Functor f, HasField s "send" a) =>
LensLike' f s a
F.send LensLike' Identity BaseCommand CommandSend
-> CommandSend -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandSend
sendCmd
 where
  sendCmd :: CommandSend
  sendCmd :: CommandSend
sendCmd = CommandSend
forall msg. Message msg => msg
defMessage
    CommandSend -> (CommandSend -> CommandSend) -> CommandSend
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSend Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "producerId" a) =>
LensLike' f s a
F.producerId LensLike' Identity CommandSend Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
pid
    CommandSend -> (CommandSend -> CommandSend) -> CommandSend
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandSend Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "sequenceId" a) =>
LensLike' f s a
F.sequenceId LensLike' Identity CommandSend Word64
-> Word64 -> CommandSend -> CommandSend
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
sid

lookup :: B.Word64 -> Topic -> BaseCommand
lookup :: Word64 -> Topic -> BaseCommand
lookup req :: Word64
req topic :: Topic
topic = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'LOOKUP
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandLookupTopic
forall (f :: * -> *) s a.
(Functor f, HasField s "lookupTopic" a) =>
LensLike' f s a
F.lookupTopic LensLike' Identity BaseCommand CommandLookupTopic
-> CommandLookupTopic -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandLookupTopic
lut
 where
  lut :: CommandLookupTopic
  lut :: CommandLookupTopic
lut = CommandLookupTopic
forall msg. Message msg => msg
defMessage
    CommandLookupTopic
-> (CommandLookupTopic -> CommandLookupTopic) -> CommandLookupTopic
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandLookupTopic Text
forall (f :: * -> *) s a.
(Functor f, HasField s "topic" a) =>
LensLike' f s a
F.topic LensLike' Identity CommandLookupTopic Text
-> Text -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. ASetter s t a b -> b -> s -> t
.~ String -> Text
T.pack (Topic -> String
forall a. Show a => a -> String
show Topic
topic)
    CommandLookupTopic
-> (CommandLookupTopic -> CommandLookupTopic) -> CommandLookupTopic
forall s t. s -> (s -> t) -> t
& LensLike' Identity CommandLookupTopic Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "requestId" a) =>
LensLike' f s a
F.requestId LensLike' Identity CommandLookupTopic Word64
-> Word64 -> CommandLookupTopic -> CommandLookupTopic
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
req

------- Keep Alive --------

ping :: BaseCommand
ping :: BaseCommand
ping = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'PING
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandPing
forall (f :: * -> *) s a.
(Functor f, HasField s "ping" a) =>
LensLike' f s a
F.ping LensLike' Identity BaseCommand CommandPing
-> CommandPing -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandPing
forall msg. Message msg => msg
defMessage

pong :: BaseCommand
pong :: BaseCommand
pong = BaseCommand
forall msg. Message msg => msg
defMessage
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand BaseCommand'Type
forall (f :: * -> *) s a.
(Functor f, HasField s "type'" a) =>
LensLike' f s a
F.type' LensLike' Identity BaseCommand BaseCommand'Type
-> BaseCommand'Type -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ BaseCommand'Type
BaseCommand'PONG
    BaseCommand -> (BaseCommand -> BaseCommand) -> BaseCommand
forall s t. s -> (s -> t) -> t
& LensLike' Identity BaseCommand CommandPong
forall (f :: * -> *) s a.
(Functor f, HasField s "pong" a) =>
LensLike' f s a
F.pong LensLike' Identity BaseCommand CommandPong
-> CommandPong -> BaseCommand -> BaseCommand
forall s t a b. ASetter s t a b -> b -> s -> t
.~ CommandPong
forall msg. Message msg => msg
defMessage

------- Metadata for Payload commands --------

messageMetadata :: MessageMetadata
messageMetadata :: MessageMetadata
messageMetadata = MessageMetadata
forall msg. Message msg => msg
defMessage